Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- (&) :: a -> (a -> b) -> b
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- makePrisms :: Name -> DecsQ
- makeClassyPrisms :: Name -> DecsQ
- makePrismLabels :: Name -> DecsQ
- type ClassyNamer = Name -> Maybe (Name, Name)
- data DefName
- type FieldNamer = Name -> [Name] -> Name -> [DefName]
- data LensRules
- makeFieldLabelsWith :: LensRules -> Name -> DecsQ
- makeFieldLabels :: Name -> DecsQ
- makeFieldLabelsFor :: [(String, String)] -> Name -> DecsQ
- declareFieldLabels :: DecsQ -> DecsQ
- declareFieldLabelsFor :: [(String, String)] -> DecsQ -> DecsQ
- declareFieldLabelsWith :: LensRules -> DecsQ -> DecsQ
- fieldLabelsRules :: LensRules
- fieldLabelsRulesFor :: [(String, String)] -> LensRules
- makeLenses :: Name -> DecsQ
- makeLensesFor :: [(String, String)] -> Name -> DecsQ
- makeLensesWith :: LensRules -> Name -> DecsQ
- declareLenses :: DecsQ -> DecsQ
- declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ
- declareLensesWith :: LensRules -> DecsQ -> DecsQ
- lensRules :: LensRules
- lensRulesFor :: [(String, String)] -> LensRules
- makeClassy :: Name -> DecsQ
- makeClassy_ :: Name -> DecsQ
- makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ
- declareClassy :: DecsQ -> DecsQ
- declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ
- classyRules :: LensRules
- classyRules_ :: LensRules
- classyRulesFor :: (String -> Maybe (String, String)) -> [(String, String)] -> LensRules
- makeFields :: Name -> DecsQ
- makeFieldsNoPrefix :: Name -> DecsQ
- declareFields :: DecsQ -> DecsQ
- defaultFieldRules :: LensRules
- declarePrisms :: DecsQ -> DecsQ
- simpleLenses :: Lens' LensRules Bool
- generateSignatures :: Lens' LensRules Bool
- generateUpdateableOptics :: Lens' LensRules Bool
- generateLazyPatterns :: Lens' LensRules Bool
- createClass :: Lens' LensRules Bool
- lensField :: Lens' LensRules FieldNamer
- lensClass :: Lens' LensRules ClassyNamer
- noPrefixFieldLabels :: LensRules
- abbreviatedFieldLabels :: LensRules
- underscoreFields :: LensRules
- camelCaseFields :: LensRules
- classUnderscoreNoPrefixFields :: LensRules
- abbreviatedFields :: LensRules
- noPrefixNamer :: FieldNamer
- underscoreNoPrefixNamer :: FieldNamer
- lookingupNamer :: [(String, String)] -> FieldNamer
- mappingNamer :: (String -> [String]) -> FieldNamer
- underscoreNamer :: FieldNamer
- camelCaseNamer :: FieldNamer
- classUnderscoreNoPrefixNamer :: FieldNamer
- abbreviatedNamer :: FieldNamer
- class ViewableOptic k r where
- type ViewResult k r :: Type
- 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
- magnifyMany :: (Is k A_Fold, Monoid c) => Optic' k is a b -> m c -> n c
- class CurryCompose (xs :: IxList)
- type family Append (xs :: [k]) (ys :: [k]) :: [k] where ...
- type family Curry (xs :: IxList) y :: Type where ...
- type WithIx i = i ': ([] :: [Type])
- type NoIx = ([] :: [Type])
- type IxList = [Type]
- data A_Review
- data A_ReversedLens
- data A_Fold
- data An_AffineFold
- data A_Getter
- data A_ReversedPrism
- data A_Setter
- data A_Traversal
- data An_AffineTraversal
- data A_Prism
- data A_Lens
- data An_Iso
- type OpticKind = Type
- type family Join k l :: OpticKind where ...
- class Is k l
- type LabelOptic' (name :: Symbol) k s a = LabelOptic name k s s a a
- 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
- labelOptic :: Optic k NoIx s t a b
- type Optic' k (is :: IxList) s a = Optic k is s s a a
- data Optic k (is :: IxList) s t a b
- castOptic :: Is srcKind destKind => Optic srcKind is s t a b -> Optic destKind is s t a b
- (%) :: (Is k m, Is l m, m ~ Join k l, ks ~ Append is js) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
- (%%) :: ks ~ Append is js => Optic k is s t u v -> Optic k js u v a b -> Optic k ks 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'
- class is ~ (i ': ([] :: [Type])) => HasSingleIndex (is :: IxList) i
- class NonEmptyIndices (is :: IxList)
- class is ~ NoIx => AcceptsEmptyIndices (f :: Symbol) (is :: IxList)
- conjoined :: HasSingleIndex is i => Optic k NoIx s t a b -> Optic k is s t a b -> Optic k is s t a b
- type Getter s a = Optic' A_Getter NoIx s a
- view :: Is k A_Getter => Optic' k is s a -> s -> a
- views :: Is k A_Getter => Optic' k is s a -> (a -> r) -> s -> r
- to :: (s -> a) -> Getter s a
- type AffineTraversalVL' s a = AffineTraversalVL s s a a
- type AffineTraversalVL s t a b = forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t
- type AffineTraversal' s a = Optic' An_AffineTraversal NoIx s a
- type AffineTraversal s t a b = Optic An_AffineTraversal NoIx s t a b
- atraversal :: (s -> Either t a) -> (s -> b -> t) -> AffineTraversal s t a b
- withAffineTraversal :: Is k An_AffineTraversal => Optic k is s t a b -> ((s -> Either t a) -> (s -> b -> t) -> r) -> r
- atraversalVL :: AffineTraversalVL s t a b -> AffineTraversal s t a b
- atraverseOf :: (Is k An_AffineTraversal, Functor f) => Optic k is s t a b -> (forall r. r -> f r) -> (a -> f b) -> s -> f t
- matching :: Is k An_AffineTraversal => Optic k is s t a b -> s -> Either t a
- unsafeFiltered :: (a -> Bool) -> AffineTraversal' a a
- type AffineFold s a = Optic' An_AffineFold NoIx s a
- afoldVL :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f u) -> s -> f v) -> AffineFold s a
- preview :: Is k An_AffineFold => Optic' k is s a -> s -> Maybe a
- previews :: Is k An_AffineFold => Optic' k is s a -> (a -> r) -> s -> Maybe r
- atraverseOf_ :: (Is k An_AffineFold, Functor f) => Optic' k is s a -> (forall r. r -> f r) -> (a -> f u) -> s -> f ()
- afolding :: (s -> Maybe a) -> AffineFold s a
- filtered :: (a -> Bool) -> AffineFold a a
- afailing :: (Is k An_AffineFold, Is l An_AffineFold) => Optic' k is s a -> Optic' l js s a -> AffineFold s a
- isn't :: Is k An_AffineFold => Optic' k is s a -> s -> Bool
- class (FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where
- itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b)
- class (FunctorWithIndex i f, Foldable f) => FoldableWithIndex i (f :: Type -> Type) | f -> i where
- class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where
- imap :: (i -> a -> b) -> f a -> f b
- itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f ()
- ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f ()
- itoList :: FoldableWithIndex i f => f a -> [(i, a)]
- ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)
- type Fold s a = Optic' A_Fold NoIx s a
- foldVL :: (forall (f :: Type -> Type). Applicative f => (a -> f u) -> s -> f v) -> Fold s a
- foldOf :: (Is k A_Fold, Monoid a) => Optic' k is s a -> s -> a
- foldMapOf :: (Is k A_Fold, Monoid m) => Optic' k is s a -> (a -> m) -> s -> m
- foldrOf :: Is k A_Fold => Optic' k is s a -> (a -> r -> r) -> r -> s -> r
- foldlOf' :: Is k A_Fold => Optic' k is s a -> (r -> a -> r) -> r -> s -> r
- toListOf :: Is k A_Fold => Optic' k is s a -> s -> [a]
- traverseOf_ :: (Is k A_Fold, Applicative f) => Optic' k is s a -> (a -> f r) -> s -> f ()
- forOf_ :: (Is k A_Fold, Applicative f) => Optic' k is s a -> s -> (a -> f r) -> f ()
- sequenceOf_ :: (Is k A_Fold, Applicative f) => Optic' k is s (f a) -> s -> f ()
- folded :: Foldable f => Fold (f a) a
- folding :: Foldable f => (s -> f a) -> Fold s a
- foldring :: (forall (f :: Type -> Type). Applicative f => (a -> f u -> f u) -> f v -> s -> f w) -> Fold s a
- unfolded :: (s -> Maybe (a, s)) -> Fold s a
- pre :: Is k A_Fold => Optic' k is s a -> AffineFold s a
- backwards_ :: Is k A_Fold => Optic' k is s a -> Fold s a
- summing :: (Is k A_Fold, Is l A_Fold) => Optic' k is s a -> Optic' l js s a -> Fold s a
- failing :: (Is k A_Fold, Is l A_Fold) => Optic' k is s a -> Optic' l js s a -> Fold s a
- has :: Is k A_Fold => Optic' k is s a -> s -> Bool
- hasn't :: Is k A_Fold => Optic' k is s a -> s -> Bool
- headOf :: Is k A_Fold => Optic' k is s a -> s -> Maybe a
- lastOf :: Is k A_Fold => Optic' k is s a -> s -> Maybe a
- andOf :: Is k A_Fold => Optic' k is s Bool -> s -> Bool
- orOf :: Is k A_Fold => Optic' k is s Bool -> s -> Bool
- anyOf :: Is k A_Fold => Optic' k is s a -> (a -> Bool) -> s -> Bool
- allOf :: Is k A_Fold => Optic' k is s a -> (a -> Bool) -> s -> Bool
- noneOf :: Is k A_Fold => Optic' k is s a -> (a -> Bool) -> s -> Bool
- productOf :: (Is k A_Fold, Num a) => Optic' k is s a -> s -> a
- sumOf :: (Is k A_Fold, Num a) => Optic' k is s a -> s -> a
- asumOf :: (Is k A_Fold, Alternative f) => Optic' k is s (f a) -> s -> f a
- msumOf :: (Is k A_Fold, MonadPlus m) => Optic' k is s (m a) -> s -> m a
- elemOf :: (Is k A_Fold, Eq a) => Optic' k is s a -> a -> s -> Bool
- notElemOf :: (Is k A_Fold, Eq a) => Optic' k is s a -> a -> s -> Bool
- lengthOf :: Is k A_Fold => Optic' k is s a -> s -> Int
- maximumOf :: (Is k A_Fold, Ord a) => Optic' k is s a -> s -> Maybe a
- minimumOf :: (Is k A_Fold, Ord a) => Optic' k is s a -> s -> Maybe a
- maximumByOf :: Is k A_Fold => Optic' k is s a -> (a -> a -> Ordering) -> s -> Maybe a
- minimumByOf :: Is k A_Fold => Optic' k is s a -> (a -> a -> Ordering) -> s -> Maybe a
- findOf :: Is k A_Fold => Optic' k is s a -> (a -> Bool) -> s -> Maybe a
- findMOf :: (Is k A_Fold, Monad m) => Optic' k is s a -> (a -> m Bool) -> s -> m (Maybe a)
- lookupOf :: (Is k A_Fold, Eq a) => Optic' k is s (a, v) -> a -> s -> Maybe v
- type IxAffineFold i s a = Optic' An_AffineFold (WithIx i) s a
- iafoldVL :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f u) -> s -> f v) -> IxAffineFold i s a
- ipreview :: (Is k An_AffineFold, HasSingleIndex is i) => Optic' k is s a -> s -> Maybe (i, a)
- ipreviews :: (Is k An_AffineFold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> r) -> s -> Maybe r
- iatraverseOf_ :: (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 ()
- iafolding :: (s -> Maybe (i, a)) -> IxAffineFold i s a
- filteredBy :: Is k An_AffineFold => Optic' k is a i -> IxAffineFold i a a
- iafailing :: (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
- type IxAffineTraversalVL' i s a = IxAffineTraversalVL i s s a a
- 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 IxAffineTraversal' i s a = Optic' An_AffineTraversal (WithIx i) s a
- type IxAffineTraversal i s t a b = Optic An_AffineTraversal (WithIx i) s t a b
- iatraversal :: (s -> Either t (i, a)) -> (s -> b -> t) -> IxAffineTraversal i s t a b
- iatraversalVL :: IxAffineTraversalVL i s t a b -> IxAffineTraversal i s t a b
- iatraverseOf :: (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
- unsafeFilteredBy :: Is k An_AffineFold => Optic' k is a i -> IxAffineTraversal' i a a
- ignored :: IxAffineTraversal i s s a b
- type IxFold i s a = Optic' A_Fold (WithIx i) s a
- ifoldVL :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f u) -> s -> f v) -> IxFold i s a
- ifoldMapOf :: (Is k A_Fold, Monoid m, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> m) -> s -> m
- ifoldrOf :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> r -> r) -> r -> s -> r
- ifoldlOf' :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> r -> a -> r) -> r -> s -> r
- itoListOf :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> s -> [(i, a)]
- itraverseOf_ :: (Is k A_Fold, Applicative f, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> f r) -> s -> f ()
- iforOf_ :: (Is k A_Fold, Applicative f, HasSingleIndex is i) => Optic' k is s a -> s -> (i -> a -> f r) -> f ()
- ifolded :: FoldableWithIndex i f => IxFold i (f a) a
- ifolding :: FoldableWithIndex i f => (s -> f a) -> IxFold i s a
- ifoldring :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f u -> f u) -> f v -> s -> f w) -> IxFold i s a
- ipre :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> IxAffineFold i s a
- ifiltered :: (Is k A_Fold, HasSingleIndex is i) => (i -> a -> Bool) -> Optic' k is s a -> IxFold i s a
- ibackwards_ :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> IxFold i s a
- isumming :: (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
- ifailing :: (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
- iheadOf :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> s -> Maybe (i, a)
- ilastOf :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> s -> Maybe (i, a)
- ianyOf :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
- iallOf :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
- inoneOf :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
- ifindOf :: (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Maybe (i, a)
- ifindMOf :: (Is k A_Fold, Monad m, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> m Bool) -> s -> m (Maybe (i, a))
- type IxGetter i s a = Optic' A_Getter (WithIx i) s a
- ito :: (s -> (i, a)) -> IxGetter i s a
- selfIndex :: IxGetter a a a
- iview :: (Is k A_Getter, HasSingleIndex is i) => Optic' k is s a -> s -> (i, a)
- iviews :: (Is k A_Getter, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> r) -> s -> r
- type IxLensVL' i s a = IxLensVL i s s a a
- type IxLensVL i s t a b = forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t
- type IxLens' i s a = Optic' A_Lens (WithIx i) s a
- type IxLens i s t a b = Optic A_Lens (WithIx i) s t a b
- ilens :: (s -> (i, a)) -> (s -> b -> t) -> IxLens i s t a b
- ilensVL :: IxLensVL i s t a b -> IxLens i s t a b
- toIxLensVL :: (Is k A_Lens, HasSingleIndex is i) => Optic k is s t a b -> IxLensVL i s t a b
- withIxLensVL :: (Is k A_Lens, HasSingleIndex is i) => Optic k is s t a b -> (IxLensVL i s t a b -> r) -> r
- devoid :: IxLens' i Void a
- type IxSetter' i s a = Optic' A_Setter (WithIx i) s a
- type IxSetter i s t a b = Optic A_Setter (WithIx i) s t a b
- iover :: (Is k A_Setter, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> b) -> s -> t
- iover' :: (Is k A_Setter, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> b) -> s -> t
- iset :: (Is k A_Setter, HasSingleIndex is i) => Optic k is s t a b -> (i -> b) -> s -> t
- iset' :: (Is k A_Setter, HasSingleIndex is i) => Optic k is s t a b -> (i -> b) -> s -> t
- isets :: ((i -> a -> b) -> s -> t) -> IxSetter i s t a b
- imapped :: FunctorWithIndex i f => IxSetter i (f a) (f b) a b
- type LensVL' s a = LensVL s s a a
- type LensVL s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Optic' A_Lens NoIx s a
- type Lens s t a b = Optic A_Lens NoIx s t a b
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- withLens :: Is k A_Lens => Optic k is s t a b -> ((s -> a) -> (s -> b -> t) -> r) -> r
- lensVL :: LensVL s t a b -> Lens s t a b
- toLensVL :: Is k A_Lens => Optic k is s t a b -> LensVL s t a b
- withLensVL :: Is k A_Lens => Optic k is s t a b -> (LensVL s t a b -> r) -> r
- equality' :: Lens a b a b
- chosen :: Lens (Either a a) (Either b b) a b
- alongside :: (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')
- united :: Lens' a ()
- type Prism' s a = Optic' A_Prism NoIx s a
- type Prism s t a b = Optic A_Prism NoIx s t a b
- prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
- prism' :: (b -> s) -> (s -> Maybe a) -> Prism s s a b
- withPrism :: Is k A_Prism => Optic k is s t a b -> ((b -> t) -> (s -> Either t a) -> r) -> r
- aside :: Is k A_Prism => Optic k is s t a b -> Prism (e, s) (e, t) (e, a) (e, b)
- without :: (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)
- below :: (Is k A_Prism, Traversable f) => Optic' k is s a -> Prism' (f s) (f a)
- only :: Eq a => a -> Prism' a ()
- nearly :: a -> (a -> Bool) -> Prism' a ()
- _Nothing :: Prism' (Maybe a) ()
- _Just :: Prism (Maybe a) (Maybe b) a b
- _Left :: Prism (Either a b) (Either c b) a c
- _Right :: Prism (Either a b) (Either a c) b c
- class ReversibleOptic k where
- type ReversedOptic k = (r :: Type) | r -> k
- re :: AcceptsEmptyIndices "re" is => Optic k is s t a b -> Optic (ReversedOptic k) is b a t s
- class ToReadOnly k s t a b where
- type ReversedLens' t b = Optic' A_ReversedLens NoIx t b
- type ReversedLens s t a b = Optic A_ReversedLens NoIx s t a b
- type ReversedPrism' s a = Optic' A_ReversedPrism NoIx s a
- type ReversedPrism s t a b = Optic A_ReversedPrism NoIx s t a b
- type Review t b = Optic' A_Review NoIx t b
- review :: Is k A_Review => Optic' k is t b -> b -> t
- unto :: (b -> t) -> Review t b
- class Bifunctor p => Swapped (p :: Type -> Type -> Type) where
- type Iso' s a = Optic' An_Iso NoIx s a
- type Iso s t a b = Optic An_Iso NoIx s t a b
- iso :: (s -> a) -> (b -> t) -> Iso s t a b
- withIso :: Iso s t a b -> ((s -> a) -> (b -> t) -> r) -> r
- au :: Functor f => Iso s t a b -> ((b -> t) -> f s) -> f a
- under :: Iso s t a b -> (t -> s) -> b -> a
- equality :: (s ~ a, t ~ b) => Iso s t a b
- simple :: Iso' a a
- coerced :: (Coercible s a, Coercible t b) => Iso s t a b
- coercedTo :: Coercible s a => Iso' s a
- coerced1 :: (Coercible s (f s), Coercible a (f a)) => Iso (f s) (f a) s a
- non :: Eq a => a -> Iso' (Maybe a) a
- non' :: Prism' a () -> Iso' (Maybe a) a
- anon :: a -> (a -> Bool) -> Iso' (Maybe a) a
- curried :: Iso ((a, b) -> c) ((d, e) -> f) (a -> b -> c) (d -> e -> f)
- uncurried :: Iso (a -> b -> c) (d -> e -> f) ((a, b) -> c) ((d, e) -> f)
- flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c')
- involuted :: (a -> a) -> Iso' a a
- class MappingOptic k (f :: Type -> Type) (g :: Type -> Type) s t a b where
- type MappedOptic k :: Type
- mapping :: AcceptsEmptyIndices "mapping" is => Optic k is s t a b -> Optic (MappedOptic k) is (f s) (g t) (f a) (g b)
- class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- _1' :: Field1 s t a b => Lens s t a b
- _2' :: Field2 s t a b => Lens s t a b
- _3' :: Field3 s t a b => Lens s t a b
- _4' :: Field4 s t a b => Lens s t a b
- _5' :: Field5 s t a b => Lens s t a b
- _6' :: Field6 s t a b => Lens s t a b
- _7' :: Field7 s t a b => Lens s t a b
- _8' :: Field8 s t a b => Lens s t a b
- _9' :: Field9 s t a b => Lens s t a b
- class AsEmpty a where
- pattern Empty :: forall a. AsEmpty a => a
- class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where
- pattern (:>) :: forall s a. Snoc s s a a => s -> a -> s
- pattern (:<) :: forall s a. Cons s s a a => a -> s -> s
- (<|) :: Cons s s a a => a -> s -> s
- cons :: Cons s s a a => a -> s -> s
- uncons :: Cons s s a a => s -> Maybe (a, s)
- _head :: Cons s s a a => AffineTraversal' s a
- _tail :: Cons s s a a => AffineTraversal' s s
- _init :: Snoc s s a a => AffineTraversal' s s
- _last :: Snoc s s a a => AffineTraversal' s a
- (|>) :: Snoc s s a a => s -> a -> s
- snoc :: Snoc s s a a => s -> a -> s
- unsnoc :: Snoc s s a a => s -> Maybe (s, a)
- type Setter' s a = Optic' A_Setter NoIx s a
- type Setter s t a b = Optic A_Setter NoIx s t a b
- over :: Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t
- over' :: Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t
- set :: Is k A_Setter => Optic k is s t a b -> b -> s -> t
- set' :: Is k A_Setter => Optic k is s t a b -> b -> s -> t
- sets :: ((a -> b) -> s -> t) -> Setter s t a b
- mapped :: Functor f => Setter (f a) (f b) a b
- (^.) :: Is k A_Getter => s -> Optic' k is s a -> a
- (^?) :: Is k An_AffineFold => s -> Optic' k is s a -> Maybe a
- (^..) :: Is k A_Fold => s -> Optic' k is s a -> [a]
- (#) :: Is k A_Review => Optic' k is t b -> b -> t
- (%~) :: Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t
- (%!~) :: Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t
- (.~) :: Is k A_Setter => Optic k is s t a b -> b -> s -> t
- (!~) :: Is k A_Setter => Optic k is s t a b -> b -> s -> t
- (?~) :: Is k A_Setter => Optic k is s t a (Maybe b) -> b -> s -> t
- (?!~) :: Is k A_Setter => Optic k is s t a (Maybe b) -> b -> s -> t
- class (Ixed m, IxKind m ~ An_AffineTraversal) => At m where
- class Ixed m where
- type family IxValue m :: Type
- class Contains m where
- type family Index s :: Type
- ixAt :: At m => Index m -> AffineTraversal' m (IxValue m)
- at' :: At m => Index m -> Lens' m (Maybe (IxValue m))
- sans :: At m => Index m -> m -> m
- type TraversalVL' s a = TraversalVL s s a a
- type TraversalVL s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t
- type Traversal' s a = Optic' A_Traversal NoIx s a
- type Traversal s t a b = Optic A_Traversal NoIx s t a b
- traversalVL :: TraversalVL s t a b -> Traversal s t a b
- traverseOf :: (Is k A_Traversal, Applicative f) => Optic k is s t a b -> (a -> f b) -> s -> f t
- forOf :: (Is k A_Traversal, Applicative f) => Optic k is s t a b -> s -> (a -> f b) -> f t
- sequenceOf :: (Is k A_Traversal, Applicative f) => Optic k is s t (f b) b -> s -> f t
- transposeOf :: Is k A_Traversal => Optic k is s t [a] a -> s -> [t]
- mapAccumLOf :: Is k A_Traversal => Optic k is s t a b -> (acc -> a -> (b, acc)) -> acc -> s -> (t, acc)
- mapAccumROf :: Is k A_Traversal => Optic k is s t a b -> (acc -> a -> (b, acc)) -> acc -> s -> (t, acc)
- scanl1Of :: Is k A_Traversal => Optic k is s t a a -> (a -> a -> a) -> s -> t
- scanr1Of :: Is k A_Traversal => Optic k is s t a a -> (a -> a -> a) -> s -> t
- failover :: Is k A_Traversal => Optic k is s t a b -> (a -> b) -> s -> Maybe t
- failover' :: Is k A_Traversal => Optic k is s t a b -> (a -> b) -> s -> Maybe t
- traversed :: Traversable t => Traversal (t a) (t b) a b
- backwards :: Is k A_Traversal => Optic k is s t a b -> Traversal s t a b
- partsOf :: Is k A_Traversal => Optic k is s t a a -> Lens s t [a] [a]
- singular :: Is k A_Traversal => Optic' k is s a -> AffineTraversal' s a
- type IxTraversalVL' i s a = IxTraversalVL i s s a a
- type IxTraversalVL i s t a b = forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t
- type IxTraversal' i s a = Optic' A_Traversal (WithIx i) s a
- type IxTraversal i s t a b = Optic A_Traversal (WithIx i) s t a b
- itraversalVL :: IxTraversalVL i s t a b -> IxTraversal i s t a b
- itraverseOf :: (Is k A_Traversal, Applicative f, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> f b) -> s -> f t
- iforOf :: (Is k A_Traversal, Applicative f, HasSingleIndex is i) => Optic k is s t a b -> s -> (i -> a -> f b) -> f t
- imapAccumLOf :: (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> (i -> acc -> a -> (b, acc)) -> acc -> s -> (t, acc)
- imapAccumROf :: (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> (i -> acc -> a -> (b, acc)) -> acc -> s -> (t, acc)
- iscanl1Of :: (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a a -> (i -> a -> a -> a) -> s -> t
- iscanr1Of :: (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a a -> (i -> a -> a -> a) -> s -> t
- ifailover :: (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> b) -> s -> Maybe t
- ifailover' :: (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> b) -> s -> Maybe t
- itraversed :: TraversableWithIndex i f => IxTraversal i (f a) (f b) a b
- indices :: (Is k A_Traversal, HasSingleIndex is i) => (i -> Bool) -> Optic k is s t a a -> IxTraversal i s t a a
- ibackwards :: (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> IxTraversal i s t a b
- elementsOf :: Is k A_Traversal => Optic k is s t a a -> (Int -> Bool) -> IxTraversal Int s t a a
- elements :: Traversable f => (Int -> Bool) -> IxTraversal' Int (f a) a
- elementOf :: Is k A_Traversal => Optic' k is s a -> Int -> IxAffineTraversal' Int s a
- element :: Traversable f => Int -> IxAffineTraversal' Int (f a) a
- ipartsOf :: (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a a -> IxLens [i] s t [a] [a]
- isingular :: (Is k A_Traversal, HasSingleIndex is i) => Optic' k is s a -> IxAffineTraversal' i s a
- class Each i s t a b | s -> i a, t -> i b, s b -> t, t a -> s where
- each :: IxTraversal i s t a b
- class IxOptic k s t a b where
- noIx :: NonEmptyIndices is => Optic k is s t a b -> Optic k NoIx s t a b
- (<%>) :: (m ~ Join k l, Is k m, Is 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
- (%>) :: (m ~ Join k l, Is k m, Is 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
- (<%) :: (m ~ Join k l, Is l m, Is k 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
- reindexed :: HasSingleIndex is i => (i -> j) -> Optic k is s t a b -> Optic k (WithIx j) s t a b
- icompose :: (i -> j -> ix) -> Optic k (i ': (j ': ([] :: [Type]))) s t a b -> Optic k (WithIx ix) s t a b
- icompose3 :: (i1 -> i2 -> i3 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': ([] :: [Type])))) s t a b -> Optic k (WithIx ix) s t a b
- icompose4 :: (i1 -> i2 -> i3 -> i4 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))) s t a b -> Optic k (WithIx ix) s t a b
- icompose5 :: (i1 -> i2 -> i3 -> i4 -> i5 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))) s t a b -> Optic k (WithIx ix) s t a b
- icomposeN :: (CurryCompose is, NonEmptyIndices is) => Curry is i -> Optic k is s t a b -> Optic k (WithIx i) s t a b
- class (Is k A_Traversal, ViewableOptic k r) => PermeableOptic k r where
- passthrough :: Optic k is s t a b -> (a -> (r, b)) -> s -> (ViewResult k r, t)
- gview :: (ViewableOptic k r, Member (Reader s) effs) => Optic' k is s r -> Sem effs (ViewResult k r)
- gviews :: (ViewableOptic k r, Member (Reader s) effs) => Optic' k is s a -> (a -> r) -> Sem effs (ViewResult k r)
- modifying :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs ()
- modifying' :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs ()
- assign :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs ()
- assign' :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs ()
- use :: (Is k A_Getter, Member (State s) effs) => Optic' k is s a -> Sem effs a
- preuse :: (Is k An_AffineFold, Member (State s) effs) => Optic' k is s a -> Sem effs (Maybe a)
- (.=) :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs ()
- (?=) :: (Is k A_Setter, Member (State s) effs) => Optic k is s s (Maybe a) (Maybe b) -> b -> Sem effs ()
- (%=) :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs ()
- (%%=) :: (PermeableOptic k r, Member (State s) effs) => Optic k is s s a b -> (a -> (r, b)) -> Sem effs (ViewResult k r)
- (<.=) :: (PermeableOptic k b, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs (ViewResult k b)
- (<?=) :: (PermeableOptic k (Maybe b), Member (State s) effs) => Optic k is s s (Maybe a) (Maybe b) -> b -> Sem effs (ViewResult k (Maybe b))
- (<%=) :: (PermeableOptic k b, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs (ViewResult k b)
- (<<.=) :: (PermeableOptic k a, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs (ViewResult k a)
- (<<?=) :: (PermeableOptic k (Maybe a), Member (State s) effs) => Optic k is s s (Maybe a) (Maybe b) -> b -> Sem effs (ViewResult k (Maybe a))
- (<<%=) :: (PermeableOptic k a, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs (ViewResult k a)
- guse :: (ViewableOptic k a, Member (State s) effs) => Optic' k is s a -> Sem effs (ViewResult k a)
- guses :: (ViewableOptic k r, Member (State s) effs) => Optic' k is s a -> (a -> r) -> Sem effs (ViewResult k r)
- zoom :: (Is k A_Lens, Member (State s) effs) => Optic' k is s a -> Sem (State a ': effs) c -> Sem effs c
- zoomMaybe :: (Is k An_AffineTraversal, Member (State s) effs) => Optic' k is s a -> Sem (State a ': effs) c -> Sem effs (Maybe c)
- glistening :: (ViewableOptic k r, Member (Writer s) effs) => Optic' k is s r -> Sem effs a -> Sem effs (a, ViewResult k r)
- glistenings :: (ViewableOptic k r, Member (Writer s) effs) => Optic' k is s a -> (a -> r) -> Sem effs b -> Sem effs (b, ViewResult k r)
Documentation
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)
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.
makePrismLabels :: Name -> DecsQ #
type ClassyNamer #
= 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.
Name to give to generated field optics.
TopName Name | Simple top-level definition name |
MethodName Name Name | makeFields-style class name and method name |
type FieldNamer #
= 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.
makeFieldLabelsWith :: LensRules -> Name -> DecsQ #
Build field optics as labels with a custom configuration.
makeFieldLabels :: Name -> DecsQ #
Build field optics as instances of LabelOptic
class for use as overloaded
labels.
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)
which can be used as #age
and #name
with language extension
OverloadedLabels.
Note: if you wonder about the form of instances or why there is no label for
animalAbsurd
, check documentation for LabelOptic
.
makeFieldOptics
=makeFieldLabelsWith
fieldLabelsRules
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")] ''FoomakeFieldLabelsFor
[("_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.
declareFieldLabelsWith :: LensRules -> DecsQ -> DecsQ #
fieldLabelsRules :: LensRules #
Rules for generation of LabelOptic
intances 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.
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")] ''FoomakeLensesFor
[("_barX", "bar"), ("_barY", "bar")] ''Bar
makeLensesWith :: LensRules -> Name -> DecsQ #
Build field optics with a custom configuration.
declareLenses :: DecsQ -> DecsQ #
declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ #
Similar to makeLensesFor
, but takes a declaration quote.
declareLensesWith :: LensRules -> DecsQ -> DecsQ #
declareLenses
with custom LensRules
.
Rules for making read-write field optics as top-level functions. It uses
underscoreNoPrefixNamer
.
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
} derivingShow
|]
will create
data Foo = FooInt
Int
derivingShow
class HasFoo t where foo ::Lens'
t Foo instance HasFoo Foo where foo =id
fooX, fooY :: HasFoo t =>Lens'
tInt
declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ #
Similar to makeClassyFor
, but takes a declaration quote.
Rules for making lenses and traversals that precompose another Lens
.
A LensRules
used by makeClassy_
.
:: (String -> Maybe (String, String)) | Type Name -> Maybe (Class Name, Method Name) |
-> [(String, String)] |
|
-> 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
declareFields :: DecsQ -> DecsQ #
declareFields =declareLensesWith
defaultFieldRules
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)
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.
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 ShowmakeLensesWith
(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.
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.
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)
.
:: (String -> [String]) | A function that maps a |
-> FieldNamer |
Create a FieldNamer
from a mapping function. If the function returns
[]
, it creates no lens for the field.
underscoreNamer :: FieldNamer #
A FieldNamer
for underscoreFields
.
camelCaseNamer :: FieldNamer #
A FieldNamer
for camelCaseFields
.
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:
- Exactly one result
a
withIso
,Lens
,ReversedPrism
andGetter
. - At most one result
Maybe a
withPrism
,AffineTraversal
andAffineFold
. - Monoidal summary of all results
Monoid a => a
withTraversal
andFold
.
When in doubt, use specific, flavour restricted versions. This function is
mostly useful for things such as passthrough
.
type ViewResult k r :: Type #
Instances
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
.
Instances
class CurryCompose (xs :: IxList) #
Class that is inhabited by all type-level lists xs
, providing the ability
to compose a function under
.Curry
xs
Instances
CurryCompose ([] :: [Type]) | |
Defined in Optics.Internal.Optic.TypeLevel | |
CurryCompose xs => CurryCompose (x ': xs) | |
Defined in Optics.Internal.Optic.TypeLevel |
Tag for a review.
Instances
ReversibleOptic A_Review | |
Defined in Optics.Re type ReversedOptic A_Review = (r :: Type) # re :: 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 | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints A_ReversedLens p -> r) -> Constraints A_Review p -> r # | |
Is A_Prism A_Review | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints A_Prism p -> r) -> Constraints A_Review p -> r # | |
Is An_Iso A_Review | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints An_Iso p -> r) -> Constraints A_Review p -> r # | |
(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Review f g s t a b | |
Defined in Optics.Mapping type MappedOptic A_Review :: Type # mapping :: 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 | |
Defined in Optics.Re | |
type MappedOptic A_Review | |
Defined in Optics.Mapping |
data A_ReversedLens #
Tag for a reversed lens.
Instances
ReversibleOptic A_ReversedLens | |
Defined in Optics.Re type ReversedOptic A_ReversedLens = (r :: Type) # re :: 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 | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints A_ReversedLens p -> r) -> Constraints A_Review p -> r # | |
Is An_Iso A_ReversedLens | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints An_Iso p -> r) -> Constraints A_ReversedLens p -> r # | |
(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedLens f g s t a b | |
Defined in Optics.Mapping type MappedOptic A_ReversedLens :: Type # mapping :: 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 | |
Defined in Optics.Re | |
type MappedOptic A_ReversedLens | |
Defined in Optics.Mapping |
Tag for a fold.
Instances
data An_AffineFold #
Tag for an affine fold.
Instances
Tag for a getter.
Instances
data A_ReversedPrism #
Tag for a reversed prism.
Instances
Tag for a setter.
Instances
Is A_Traversal A_Setter | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints A_Traversal p -> r) -> Constraints A_Setter p -> r # | |
Is An_AffineTraversal A_Setter | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints An_AffineTraversal p -> r) -> Constraints A_Setter p -> r # | |
Is A_Prism A_Setter | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints A_Prism p -> r) -> Constraints A_Setter p -> r # | |
Is A_Lens A_Setter | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints A_Lens p -> r) -> Constraints A_Setter p -> r # | |
Is An_Iso A_Setter | |
Defined in Optics.Internal.Optic.Subtyping implies :: (Constraints An_Iso p -> r) -> Constraints A_Setter p -> r # | |
IxOptic A_Setter s t a b | |
Defined in Optics.Indexed.Core |
data A_Traversal #
Tag for a traversal.
Instances
data An_AffineTraversal #
Tag for an affine traversal.
Instances
Tag for a prism.
Instances
Tag for a lens.
Instances
Tag for an iso.
Instances
type family Join k l :: OpticKind where ... #
Computes the least upper bound of two optics kinds.
Join k l
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 (Join k l)
.
Subtyping relationship between kinds of optics.
An instance of
means that any Is
k l
can be used
as an Optic
k
. For example, we have an Optic
l
instance, but not Is
A_Lens
A_Traversal
.Is
A_Traversal
A_Lens
This class needs instances for all possible combinations of tags.
Instances
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 of
.LabelOptic
"foo" k s t a b
See Optics.Label for examples and further details.
labelOptic :: Optic k NoIx s t a b #
Used to interpret overloaded label syntax. An overloaded label #foo
corresponds to
.labelOptic
@"foo"
Instances
(LabelOptic name k s t a b, GeneralLabelOptic name k s t a b (AnyHasRep (Rep s) (Rep t))) => LabelOptic name k s t a b | If no instance matches, fall back on |
Defined in Optics.Internal.Optic 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 |
Defined in Optics.Internal.Optic labelOptic :: Optic k NoIx Void0 Void0 a b # |
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.
Instances
(LabelOptic name k s t a b, is ~ NoIx) => IsLabel name (Optic k is s t a b) | |
Defined in Optics.Internal.Optic |
(%) :: (Is k m, Is l m, m ~ Join k l, ks ~ Append is js) => 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.
(%%) :: ks ~ Append is js => 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.
(%&) :: 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 ': ([] :: [Type])) => 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
((TypeError (Text "Indexed optic is expected") :: Constraint), ([] :: [Type]) ~ (i ': ([] :: [Type]))) => HasSingleIndex ([] :: [Type]) i | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use (<%>) or icompose to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': ([] :: [Type]))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': ([] :: [Type]))) i | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use icompose3 to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': ([] :: [Type])))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': ([] :: [Type])))) i | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use icompose4 to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))) i | |
Defined in Optics.Internal.Indexed | |
((TypeError (Text "Use icompose5 to flatten indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))) i | |
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 ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))) i | |
Defined in Optics.Internal.Indexed | |
HasSingleIndex (i ': ([] :: [Type])) i | |
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
(TypeError (Text "Indexed optic is expected") :: Constraint) => NonEmptyIndices ([] :: [Type]) | |
Defined in Optics.Internal.Indexed | |
NonEmptyIndices (x ': xs) | |
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
AcceptsEmptyIndices f ([] :: [Type]) | |
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) | |
Defined in Optics.Internal.Indexed |
conjoined :: HasSingleIndex is i => Optic k NoIx s t a b -> Optic k is s t a b -> Optic k is s t a b #
views :: Is k A_Getter => Optic' k is s a -> (a -> r) -> s -> r #
View the function of the value pointed to by a getter.
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 :: 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 :: (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
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 =
the second unsafeFiltered
even
Traversal
law is violated:
over
evenssucc
.
over
evenssucc
/=
over
evens (succ
.
succ
)
So, in order for this to qualify as a legal Traversal
you
can only use it for actions that preserve the result of the predicate!
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_
.
afoldVL
≡id
Since: optics-core-0.3
preview :: 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 :: 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_ :: (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 :: (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 :: 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
class (FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where #
Class for Traversable
s that have an additional read-only index available.
itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b) #
Instances
class (FunctorWithIndex i f, Foldable f) => FoldableWithIndex i (f :: Type -> Type) | f -> i where #
Class for Foldable
s that have an additional read-only index available.
Nothing
Instances
class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where #
Class for Functor
s that have an additional read-only index available.
Nothing
Instances
itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f () #
Traverse FoldableWithIndex
ignoring the results.
ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f () #
Flipped itraverse_
.
itoList :: FoldableWithIndex i f => f a -> [(i, a)] #
List of elements of a structure with an index, from left to right.
ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b) #
Flipped itraverse
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_
.
foldVL
≡id
foldOf :: (Is k A_Fold, Monoid a) => Optic' k is s a -> s -> a #
Combine the results of a fold using a monoid.
foldMapOf :: (Is k A_Fold, Monoid m) => Optic' k is s a -> (a -> m) -> s -> m #
Fold via embedding into a monoid.
foldrOf :: Is k A_Fold => Optic' k is s a -> (a -> r -> r) -> r -> s -> r #
Fold right-associatively.
foldlOf' :: Is k A_Fold => Optic' k is s a -> (r -> a -> r) -> r -> s -> r #
Fold left-associatively, and strictly.
toListOf :: 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_ :: (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_ :: (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_ :: (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
foldring :: (forall (f :: Type -> Type). Applicative f => (a -> f u -> f u) -> f v -> s -> f w) -> Fold s a #
pre :: 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_ :: 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 :: (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]
failing :: (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]
lengthOf :: 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.
length
≡lengthOf
folded
>>>
lengthOf _1 ("hello",())
1
>>>
lengthOf folded [1..10]
10
>>>
lengthOf (folded % folded) [[1,2],[3,4],[5,6]]
6
maximumOf :: (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
maximum
≡fromMaybe
(error
"empty").
maximumOf
folded
In the interest of efficiency, This operation has semantics more strict than
strictly necessary. \o ->
has lazier
semantics but could leak memory.getMax
. foldMapOf
o Max
minimumOf :: (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
minimum
≡fromMaybe
(error
"empty").
minimumOf
folded
In the interest of efficiency, This operation has semantics more strict than
strictly necessary. \o ->
has lazier
semantics but could leak memory.getMin
. foldMapOf
o Min
maximumByOf :: 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 :: 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
findMOf :: (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 :: (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'
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_
.
iafoldVL
≡id
Since: optics-core-0.3
ipreview :: (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 :: (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_ :: (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 :: 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 :: (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 :: (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 :: 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 (seeunsafeFiltered
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
or
IxAffineFold
is viewed as a monoid.
>>>
6 & ignored %~ absurd
6
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_
.
ifoldVL
≡id
ifoldMapOf :: (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 :: (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' :: (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 :: (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_ :: (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_ :: (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 #
ipre :: (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 :: (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_ :: (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 :: (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")]
ifailing :: (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 :: (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 :: (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)
ifindOf :: (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 :: (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.
ito :: (s -> (i, a)) -> IxGetter i s a #
Build an indexed getter from a function.
>>>
iview (ito id) ('i', 'x')
('i','x')
Use a value itself as its own index. This is essentially an indexed version
of equality
.
iview :: (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 :: (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 t a b = Optic A_Lens (WithIx i) s t a b #
Type synonym for a type-modifying indexed lens.
ilensVL :: IxLensVL i s t a b -> IxLens i s t a b #
Build an indexed lens from the van Laarhoven representation.
toIxLensVL :: (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 :: (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.
There is an indexed field for every type in the Void
.
>>>
set (mapped % devoid) 1 []
[]
>>>
over (_Just % devoid) abs Nothing
Nothing
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 :: (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' :: (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' :: (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
imapped
≡imap
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.
toLensVL :: 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 :: 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.
alongside :: (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')
We can always retrieve a ()
from any type.
>>>
view united "hello"
()
>>>
set united () "hello"
"hello"
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.
withPrism :: 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 :: 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 :: (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) #
below :: (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
.
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.
class ReversibleOptic k where #
Class for optics that can be re
versed.
type ReversedOptic k = (r :: Type) | r -> k #
Injective type family that maps an optic kind to the optic kind produced
by re
versing it.
ReversedOptic
An_Iso
=An_Iso
ReversedOptic
A_Prism
=A_ReversedPrism
ReversedOptic
A_ReversedPrism
=A_Prism
ReversedOptic
A_Lens
=A_ReversedLens
ReversedOptic
A_ReversedLens
=A_Lens
ReversedOptic
A_Getter
=A_Review
ReversedOptic
A_Review
=A_Getter
re :: 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
class ToReadOnly k s t a b where #
Class for read-write optics that have their read-only counterparts.
getting :: Optic k is s t a b -> Optic' (Join A_Getter 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 ::
of read-write
kind Optic
k is s t a bk
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
(s ~ t, a ~ b) => ToReadOnly A_Fold s t a b | |
(s ~ t, a ~ b) => ToReadOnly An_AffineFold s t a b | |
Defined in Optics.ReadOnly getting :: Optic An_AffineFold is s t a b -> Optic' (Join A_Getter An_AffineFold) is s a # | |
(s ~ t, a ~ b) => ToReadOnly A_Getter s t a b | |
ToReadOnly A_ReversedPrism s t a b | |
Defined in Optics.ReadOnly getting :: Optic A_ReversedPrism is s t a b -> Optic' (Join A_Getter A_ReversedPrism) is s a # | |
ToReadOnly A_Traversal s t a b | |
Defined in Optics.ReadOnly getting :: Optic A_Traversal is s t a b -> Optic' (Join A_Getter A_Traversal) is s a # | |
ToReadOnly An_AffineTraversal s t a b | |
Defined in Optics.ReadOnly getting :: Optic An_AffineTraversal is s t a b -> Optic' (Join A_Getter An_AffineTraversal) is s a # | |
ToReadOnly A_Prism s t a b | |
ToReadOnly A_Lens s t a b | |
ToReadOnly An_Iso s t a b | |
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.
review :: Is k A_Review => Optic' k is t b -> b -> t #
Retrieve the value targeted by a Review
.
>>>
review _Left "hi"
Left "hi"
class Bifunctor p => Swapped (p :: Type -> Type -> Type) where #
This class provides for symmetric bifunctors.
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.
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
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 :: 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 :: (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
is an isomorphism from non
v
to Maybe
a'a
.
non
≡non'
.
only
Keep in mind this is only a real isomorphism if you treat the domain as being
.Maybe
(a sans v)
This is practically quite useful when you want to have a Map
where
all the entries should have non-zero values.
>>>
Map.fromList [("hello",1)] & at "hello" % non 0 %~ (+2)
fromList [("hello",3)]
>>>
Map.fromList [("hello",1)] & at "hello" % non 0 %~ (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 #
generalizes non'
p
to take any unit non
(p # ())Prism
This function generates an isomorphism between
and Maybe
(a | isn't
p a)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 #
generalizes anon
a p
to take any value and a predicate.non
a
anon
a ≡non'
.
nearly
a
This function assumes that p a
holds
and generates an isomorphism
between True
and Maybe
(a | not
(p a))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
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)
class MappingOptic k (f :: Type -> Type) (g :: Type -> Type) s t a b where #
type MappedOptic k :: Type #
Type family that maps an optic to the optic kind produced by
mapping
using it.
mapping :: AcceptsEmptyIndices "mapping" is => Optic k is s t a b -> Optic (MappedOptic k) is (f s) (g t) (f a) (g b) #
Instances
(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Review f g s t a b | |
Defined in Optics.Mapping type MappedOptic A_Review :: Type # mapping :: 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 | |
Defined in Optics.Mapping type MappedOptic A_ReversedLens :: Type # mapping :: 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 |
|
Defined in Optics.Mapping type MappedOptic A_Getter :: Type # mapping :: 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 | |
Defined in Optics.Mapping type MappedOptic A_ReversedPrism :: Type # mapping :: 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 | |
Defined in Optics.Mapping type MappedOptic A_Prism :: Type # mapping :: 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 | |
Defined in Optics.Mapping type MappedOptic A_Lens :: Type # mapping :: 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 | |
Defined in Optics.Mapping type MappedOptic An_Iso :: Type # mapping :: AcceptsEmptyIndices "mapping" is => Optic An_Iso is s t a b -> Optic (MappedOptic An_Iso) is (f s) (g t) (f a) (g 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.
Nothing
Instances
Field9 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i') i i' | |
Defined in Data.Tuple.Optics |
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.
Nothing
Instances
Field8 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h') h h' | |
Defined in Data.Tuple.Optics | |
Field8 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h', i) h h' | |
Defined in Data.Tuple.Optics |
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.
Nothing
Instances
Field7 (a, b, c, d, e, f, g) (a, b, c, d, e, f, g') g g' | |
Defined in Data.Tuple.Optics | |
Field7 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g', h) g g' | |
Defined in Data.Tuple.Optics | |
Field7 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g', h, i) g g' | |
Defined in Data.Tuple.Optics |
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.
Nothing
Instances
Field6 (a, b, c, d, e, f) (a, b, c, d, e, f') f f' | |
Defined in Data.Tuple.Optics | |
Field6 (a, b, c, d, e, f, g) (a, b, c, d, e, f', g) f f' | |
Defined in Data.Tuple.Optics | |
Field6 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f', g, h) f f' | |
Defined in Data.Tuple.Optics | |
Field6 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f', g, h, i) f f' | |
Defined in Data.Tuple.Optics |
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.
Nothing
Instances
Field5 (a, b, c, d, e) (a, b, c, d, e') e e' | |
Defined in Data.Tuple.Optics | |
Field5 (a, b, c, d, e, f) (a, b, c, d, e', f) e e' | |
Defined in Data.Tuple.Optics | |
Field5 (a, b, c, d, e, f, g) (a, b, c, d, e', f, g) e e' | |
Defined in Data.Tuple.Optics | |
Field5 (a, b, c, d, e, f, g, h) (a, b, c, d, e', f, g, h) e e' | |
Defined in Data.Tuple.Optics | |
Field5 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e', f, g, h, i) e e' | |
Defined in Data.Tuple.Optics |
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.
Nothing
Instances
Field4 (a, b, c, d) (a, b, c, d') d d' | |
Defined in Data.Tuple.Optics | |
Field4 (a, b, c, d, e) (a, b, c, d', e) d d' | |
Defined in Data.Tuple.Optics | |
Field4 (a, b, c, d, e, f) (a, b, c, d', e, f) d d' | |
Defined in Data.Tuple.Optics | |
Field4 (a, b, c, d, e, f, g) (a, b, c, d', e, f, g) d d' | |
Defined in Data.Tuple.Optics | |
Field4 (a, b, c, d, e, f, g, h) (a, b, c, d', e, f, g, h) d d' | |
Defined in Data.Tuple.Optics | |
Field4 (a, b, c, d, e, f, g, h, i) (a, b, c, d', e, f, g, h, i) d d' | |
Defined in Data.Tuple.Optics |
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.
Nothing
Instances
Field3 (a, b, c) (a, b, c') c c' | |
Defined in Data.Tuple.Optics | |
Field3 (a, b, c, d) (a, b, c', d) c c' | |
Defined in Data.Tuple.Optics | |
Field3 (a, b, c, d, e) (a, b, c', d, e) c c' | |
Defined in Data.Tuple.Optics | |
Field3 (a, b, c, d, e, f) (a, b, c', d, e, f) c c' | |
Defined in Data.Tuple.Optics | |
Field3 (a, b, c, d, e, f, g) (a, b, c', d, e, f, g) c c' | |
Defined in Data.Tuple.Optics | |
Field3 (a, b, c, d, e, f, g, h) (a, b, c', d, e, f, g, h) c c' | |
Defined in Data.Tuple.Optics | |
Field3 (a, b, c, d, e, f, g, h, i) (a, b, c', d, e, f, g, h, i) c c' | |
Defined in Data.Tuple.Optics |
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.
Nothing
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
Field2 (a, b) (a, b') b b' | |
Defined in Data.Tuple.Optics | |
Field2 (a, b, c) (a, b', c) b b' | |
Defined in Data.Tuple.Optics | |
Field2 (a, b, c, d) (a, b', c, d) b b' | |
Defined in Data.Tuple.Optics | |
Field2 ((f :*: g) p) ((f :*: g') p) (g p) (g' p) | |
Field2 (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' | |
Defined in Data.Tuple.Optics | |
Field2 (a, b, c, d, e, f) (a, b', c, d, e, f) b b' | |
Defined in Data.Tuple.Optics | |
Field2 (a, b, c, d, e, f, g) (a, b', c, d, e, f, g) b b' | |
Defined in Data.Tuple.Optics | |
Field2 (a, b, c, d, e, f, g, h) (a, b', c, d, e, f, g, h) b b' | |
Defined in Data.Tuple.Optics | |
Field2 (a, b, c, d, e, f, g, h, i) (a, b', c, d, e, f, g, h, i) b b' | |
Defined in Data.Tuple.Optics |
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.
Nothing
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
Field1 (Identity a) (Identity b) a b | |
Field1 (a, b) (a', b) a a' | |
Defined in Data.Tuple.Optics | |
Field1 (a, b, c) (a', b, c) a a' | |
Defined in Data.Tuple.Optics | |
Field1 (a, b, c, d) (a', b, c, d) a a' | |
Defined in Data.Tuple.Optics | |
Field1 ((f :*: g) p) ((f' :*: g) p) (f p) (f' p) | |
Field1 (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' | |
Defined in Data.Tuple.Optics | |
Field1 (a, b, c, d, e, f) (a', b, c, d, e, f) a a' | |
Defined in Data.Tuple.Optics | |
Field1 (a, b, c, d, e, f, g) (a', b, c, d, e, f, g) a a' | |
Defined in Data.Tuple.Optics | |
Field1 (a, b, c, d, e, f, g, h) (a', b, c, d, e, f, g, h) a a' | |
Defined in Data.Tuple.Optics | |
Field1 (a, b, c, d, e, f, g, h, i) (a', b, c, d, e, f, g, h, i) a a' | |
Defined in Data.Tuple.Optics |
Class for types that may be _Empty
.
Nothing
Instances
pattern Empty :: forall a. AsEmpty a => a #
Pattern synonym for matching on any type with an AsEmpty
instance.
>>>
case Nothing of { Empty -> True; _ -> False }
True
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.
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.
pattern (:>) :: forall s a. 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 (:<) :: forall s a. 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'
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 :: 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
over' :: 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' :: 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.
(^?) :: Is k An_AffineFold => s -> Optic' k is s a -> Maybe a infixl 8 #
Flipped infix version of preview
.
(%!~) :: Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t infixr 4 #
Infix version of over'
.
(?!~) :: 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
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.
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
.
Nothing
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
.
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
Ixed IntSet | |
Ixed [a] | |
Ixed (Maybe a) | |
Ixed (Identity a) | |
Ixed (NonEmpty a) | |
Ixed (IntMap a) | |
Ixed (Tree a) | |
Ixed (Seq a) | |
Ord k => Ixed (Set k) | |
Eq e => Ixed (e -> a) | |
a0 ~ a1 => Ixed (a0, a1) | |
(IArray UArray e, Ix i) => Ixed (UArray i e) | arr |
Ix i => Ixed (Array i e) | arr |
Ord k => Ixed (Map k a) | |
(a0 ~ a1, a0 ~ a2) => Ixed (a0, a1, a2) | |
(a0 ~ a1, a0 ~ a2, a0 ~ a3) => Ixed (a0, a1, a2, a3) | |
(a0 ~ a1, a0 ~ a2, a0 ~ a3, a0 ~ a4) => Ixed (a0, a1, a2, a3, a4) | |
(a0 ~ a1, a0 ~ a2, a0 ~ a3, a0 ~ a4, a0 ~ a5) => Ixed (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) | |
(a0 ~ a1, a0 ~ a2, a0 ~ a3, a0 ~ a4, a0 ~ a5, a0 ~ a6, a0 ~ a7) => Ixed (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) | |
type family IxValue m :: Type #
Type family that takes a key-value container type and returns the type of
values stored in the container, for example
. This
is shared by both IxValue
(Map
k a) ~ aIxed
and At
.
Instances
type IxValue ByteString | |
Defined in Optics.At | |
type IxValue ByteString | |
Defined in Optics.At | |
type IxValue IntSet | |
Defined in Optics.At.Core | |
type IxValue Text | |
type IxValue Text | |
type IxValue [a] | |
Defined in Optics.At.Core type IxValue [a] = a | |
type IxValue (Maybe a) | |
Defined in Optics.At.Core | |
type IxValue (Identity a) | |
Defined in Optics.At.Core | |
type IxValue (NonEmpty a) | |
Defined in Optics.At.Core | |
type IxValue (IntMap a) | |
Defined in Optics.At.Core | |
type IxValue (Tree a) | |
Defined in Optics.At.Core | |
type IxValue (Seq a) | |
Defined in Optics.At.Core | |
type IxValue (Set k) | |
Defined in Optics.At.Core | |
type IxValue (Vector a) | |
type IxValue (Vector a) | |
type IxValue (Vector a) | |
type IxValue (HashSet k) | |
type IxValue (Vector a) | |
type IxValue (e -> a) | |
Defined in Optics.At.Core type IxValue (e -> a) = a | |
type IxValue (a0, a2) |
|
Defined in Optics.At.Core type IxValue (a0, a2) = a0 | |
type IxValue (UArray i e) | |
Defined in Optics.At.Core | |
type IxValue (Array i e) | |
Defined in Optics.At.Core | |
type IxValue (Map k a) | |
Defined in Optics.At.Core | |
type IxValue (HashMap k a) | |
type IxValue (a0, a1, a2) |
|
Defined in Optics.At.Core type IxValue (a0, a1, a2) = a0 | |
type IxValue (a0, a1, a2, a3) |
|
Defined in Optics.At.Core type IxValue (a0, a1, a2, a3) = a0 | |
type IxValue (a0, a1, a2, a3, a4) |
|
Defined in Optics.At.Core type IxValue (a0, a1, a2, a3, a4) = a0 | |
type IxValue (a0, a1, a2, a3, a4, a5) |
|
Defined in Optics.At.Core type IxValue (a0, a1, a2, a3, a4, a5) = a0 | |
type IxValue (a0, a1, a2, a3, a4, a5, a6) |
|
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) |
|
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) |
|
Defined in Optics.At.Core type IxValue (a0, a1, a2, a3, a4, a5, a6, a7, a8) = a0 |
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.
Type family that takes a key-value container type and returns the type of
keys (indices) into the container, for example
.
This is shared by Index
(Map
k a) ~ kIxed
, At
and Contains
.
Instances
type Index ByteString | |
Defined in Optics.At | |
type Index ByteString | |
Defined in Optics.At | |
type Index IntSet | |
Defined in Optics.At.Core | |
type Index Text | |
type Index Text | |
type Index [a] | |
Defined in Optics.At.Core | |
type Index (Maybe a) | |
Defined in Optics.At.Core | |
type Index (Complex a) | |
Defined in Optics.At.Core | |
type Index (Identity a) | |
Defined in Optics.At.Core | |
type Index (NonEmpty a) | |
Defined in Optics.At.Core | |
type Index (IntMap a) | |
Defined in Optics.At.Core | |
type Index (Tree a) | |
Defined in Optics.At.Core | |
type Index (Seq a) | |
Defined in Optics.At.Core | |
type Index (Set a) | |
Defined in Optics.At.Core | |
type Index (Vector a) | |
type Index (Vector a) | |
type Index (Vector a) | |
type Index (HashSet a) | |
type Index (Vector a) | |
type Index (e -> a) | |
Defined in Optics.At.Core type Index (e -> a) = e | |
type Index (a, b) | |
Defined in Optics.At.Core | |
type Index (UArray i e) | |
Defined in Optics.At.Core | |
type Index (Array i e) | |
Defined in Optics.At.Core | |
type Index (Map k a) | |
Defined in Optics.At.Core | |
type Index (HashMap k a) | |
type Index (a, b, c) | |
Defined in Optics.At.Core | |
type Index (a, b, c, d) | |
Defined in Optics.At.Core | |
type Index (a, b, c, d, e) | |
Defined in Optics.At.Core | |
type Index (a, b, c, d, e, f) | |
Defined in Optics.At.Core | |
type Index (a, b, c, d, e, f, g) | |
Defined in Optics.At.Core | |
type Index (a, b, c, d, e, f, g, h) | |
Defined in Optics.At.Core | |
type Index (a, b, c, d, e, f, g, h, i) | |
Defined in Optics.At.Core |
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 ...
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
.
traverseOf
≡id
traverseOf
.
traversalVL
≡id
traverseOf :: (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 :: (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 :: (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)]
sequence
≡sequenceOf
traversed
≡traverse
id
sequenceOf
o ≡traverseOf
oid
transposeOf :: Is k A_Traversal => Optic k is s t [a] a -> s -> [t] #
mapAccumLOf :: 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
.
mapAccumL
≡mapAccumLOf
traverse
mapAccumLOf
accumulates State
from left to right.
mapAccumROf :: 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
.
mapAccumR
≡mapAccumROf
traversed
mapAccumROf
accumulates State
from right to left.
scanl1Of :: Is k A_Traversal => Optic k is s t a a -> (a -> a -> a) -> s -> t #
scanr1Of :: Is k A_Traversal => Optic k is s t a a -> (a -> a -> a) -> s -> t #
failover :: 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' :: 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
backwards :: 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 :: 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 :: 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
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
.
itraverseOf
≡id
itraverseOf
.
itraversalVL
≡id
itraverseOf :: (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 :: (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 :: (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 :: (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 :: (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 :: (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 :: (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' :: (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
itraversed
≡itraverse
>>>
iover (itraversed <%> itraversed) (,) ["ab", "cd"]
[[((0,0),'a'),((0,1),'b')],[((1,0),'c'),((1,1),'d')]]
indices :: (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 :: (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 :: 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.
elements
≡elementsOf
traverse
elementOf :: 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.
element
≡elementOf
traversed
ipartsOf :: (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 :: (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
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)
Nothing
each :: IxTraversal i s t a b #
Instances
Each Int [a] [b] a b |
|
Defined in Optics.Each.Core each :: IxTraversal Int [a] [b] a b # | |
Each Int (NonEmpty a) (NonEmpty b) a b |
|
Defined in Optics.Each.Core | |
Each Int (IntMap a) (IntMap b) a b |
|
Defined in Optics.Each.Core | |
Each Int (Seq a) (Seq b) a b |
|
Defined in Optics.Each.Core | |
Each () (Maybe a) (Maybe b) a b |
|
Defined in Optics.Each.Core each :: IxTraversal () (Maybe a) (Maybe b) a b # | |
Each () (Identity a) (Identity b) a b |
|
Defined in Optics.Each.Core each :: IxTraversal () (Identity a) (Identity b) a b # | |
(a ~ a1, b ~ b1) => Each Int (a, a1) (b, b1) a b |
|
Defined in Optics.Each.Core each :: IxTraversal Int (a, a1) (b, b1) a b # | |
k ~ k' => Each k (Map k a) (Map k' b) a b |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core 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 |
|
Defined in Optics.Each.Core | |
Each (Either () ()) (Complex a) (Complex b) a b |
|
Defined in Optics.Each.Core | |
(a ~ a', b ~ b') => Each (Either () ()) (Either a a') (Either b b') a b |
|
Defined in Optics.Each.Core |
class IxOptic k s t a b where #
Class for optic kinds that can have indices.
noIx :: 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
(s ~ t, a ~ b) => IxOptic A_Fold s t a b | |
Defined in Optics.Indexed.Core | |
(s ~ t, a ~ b) => IxOptic An_AffineFold s t a b | |
Defined in Optics.Indexed.Core noIx :: 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 | |
Defined in Optics.Indexed.Core | |
IxOptic A_Setter s t a b | |
Defined in Optics.Indexed.Core | |
IxOptic A_Traversal s t a b | |
Defined in Optics.Indexed.Core noIx :: 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 | |
Defined in Optics.Indexed.Core noIx :: 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 | |
Defined in Optics.Indexed.Core |
(<%>) :: (m ~ Join k l, Is k m, Is 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')]
(%>) :: (m ~ Join k l, Is k m, Is 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')]
(<%) :: (m ~ Join k l, Is l m, Is k 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 :: 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 ': ([] :: [Type]))) 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 ': ([] :: [Type])))) 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 ': ([] :: [Type]))))) 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 ': ([] :: [Type])))))) s t a b -> Optic k (WithIx ix) s t a b #
Flatten indices obtained from five indexed optics.
icomposeN :: (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 (Is k A_Traversal, ViewableOptic k r) => PermeableOptic k r where #
passthrough :: 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
Monoid r => PermeableOptic A_Traversal r | |
Defined in Optics.Passthrough passthrough :: Optic A_Traversal is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Traversal r, t) # | |
PermeableOptic An_AffineTraversal r | |
Defined in Optics.Passthrough passthrough :: Optic An_AffineTraversal is s t a b -> (a -> (r, b)) -> s -> (ViewResult An_AffineTraversal r, t) # | |
PermeableOptic A_Prism r | |
Defined in Optics.Passthrough passthrough :: Optic A_Prism is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Prism r, t) # | |
PermeableOptic A_Lens r | |
Defined in Optics.Passthrough passthrough :: Optic A_Lens is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Lens r, t) # | |
PermeableOptic An_Iso r | |
Defined in Optics.Passthrough passthrough :: 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 #
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 #