optics-core-0.2: Optics as an abstract interface: core definitions

Safe HaskellNone
LanguageHaskell2010

Optics.IxFold

Contents

Description

An IxFold is an indexed version of a Fold. See the "Indexed optics" section of the overview documentation in the Optics module of the main optics package for more details on indexed optics.

Synopsis

Formation

type IxFold i s a = Optic' A_Fold (WithIx i) s a Source #

Type synonym for an indexed fold.

Introduction

ifoldVL :: (forall f. Applicative f => (i -> a -> f u) -> s -> f v) -> IxFold i s a Source #

Obtain an indexed fold by lifting itraverse_ like function.

ifoldVL . itraverseOf_id
itraverseOf_ . ifoldVLid

Elimination

ifoldMapOf :: (Is k A_Fold, Monoid m, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> m) -> s -> m Source #

Fold with index via embedding into a monoid.

ifoldrOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> r -> r) -> r -> s -> r Source #

Fold with index right-associatively.

ifoldlOf' :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> r -> a -> r) -> r -> s -> r Source #

Fold with index left-associatively, and strictly.

itoListOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> s -> [(i, a)] Source #

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, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> f r) -> s -> f () Source #

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, is `HasSingleIndex` i) => Optic' k is s a -> s -> (i -> a -> f r) -> f () Source #

A version of itraverseOf_ with the arguments flipped.

Additional introduction forms

ifolded :: FoldableWithIndex i f => IxFold i (f a) a Source #

Indexed fold via FoldableWithIndex class.

ifolding :: FoldableWithIndex i f => (s -> f a) -> IxFold i s a Source #

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. Applicative f => (i -> a -> f u -> f u) -> f v -> s -> f w) -> IxFold i s a Source #

Obtain an IxFold by lifting ifoldr like function.

>>> itoListOf (ifoldring ifoldr) "hello"
[(0,'h'),(1,'e'),(2,'l'),(3,'l'),(4,'o')]

Additional elimination forms

See also toMapOf, which constructs a Map from an IxFold.

iheadOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> s -> Maybe (i, a) Source #

Retrieve the first entry of an IxFold along with its index.

>>> iheadOf ifolded [1..10]
Just (0,1)

ilastOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> s -> Maybe (i, a) Source #

Retrieve the last entry of an IxFold along with its index.

>>> ilastOf ifolded [1..10]
Just (9,10)

ianyOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool Source #

Return whether or not any element viewed through an IxFold satisfies a predicate, with access to the i.

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

anyOf o ≡ ianyOf o . const

iallOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool Source #

Return whether or not all elements viewed through an IxFold satisfy a predicate, with access to the i.

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

allOf o ≡ iallOf o . const

inoneOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool Source #

Return whether or not none of the elements viewed through an IxFold satisfy a predicate, with access to the i.

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

noneOf o ≡ inoneOf o . const

ifindOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Maybe (i, a) Source #

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, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> m Bool) -> s -> m (Maybe (i, a)) Source #

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.

Combinators

ipre :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> IxAffineFold i s a Source #

Convert an indexed fold to an IxAffineFold that visits the first element of the original fold.

ifiltered :: (Is k A_Fold, is `HasSingleIndex` i) => (i -> a -> Bool) -> Optic' k is s a -> IxFold i s a Source #

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, is `HasSingleIndex` i) => Optic' k is s a -> IxFold i s a Source #

This allows you to traverse the elements of an IxFold in the opposite order.

Semigroup structure

isumming :: (Is k A_Fold, Is l A_Fold, is1 `HasSingleIndex` i, is2 `HasSingleIndex` i) => Optic' k is1 s a -> Optic' l is2 s a -> IxFold i s a infixr 6 Source #

Return entries of the first IxFold, then the second one.

ifailing :: (Is k A_Fold, Is l A_Fold, is1 `HasSingleIndex` i, is2 `HasSingleIndex` i) => Optic' k is1 s a -> Optic' l is2 s a -> IxFold i s a infixl 3 Source #

Try the first IxFold. If it returns no entries, try the second one.

Subtyping

data A_Fold :: OpticKind Source #

Tag for a fold.

Instances
Is An_AffineFold A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Getter A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Getter A_Fold p -> (Constraints A_Getter p -> r) -> Constraints A_Fold p -> r Source #

Is A_ReversedPrism A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Traversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Traversal A_Fold p -> (Constraints A_Traversal p -> r) -> Constraints A_Fold p -> r Source #

Is An_AffineTraversal A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Is A_Prism A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Prism A_Fold p -> (Constraints A_Prism p -> r) -> Constraints A_Fold p -> r Source #

Is A_Lens A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy A_Lens A_Fold p -> (Constraints A_Lens p -> r) -> Constraints A_Fold p -> r Source #

Is An_Iso A_Fold Source # 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: proxy An_Iso A_Fold p -> (Constraints An_Iso p -> r) -> Constraints A_Fold p -> r Source #

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

Defined in Optics.ReadOnly

Methods

getting :: Optic A_Fold is s t a b -> Optic' (Join A_Getter A_Fold) is s a Source #

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

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic A_Fold is s t a b -> Optic A_Fold NoIx s t a b Source #

Re-exports

class (FunctorWithIndex i f, Foldable f) => FoldableWithIndex i f | f -> i where Source #

Class for Foldables that have an additional read-only index available.

Minimal complete definition

Nothing

Methods

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

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

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

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

Instances
FoldableWithIndex Int [] Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex Int ZipList Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex Int NonEmpty Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex Int IntMap Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex Int Seq Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex () Maybe Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex () Par1 Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex () Identity Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex k (Map k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex k ((,) k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

FoldableWithIndex [Int] Tree Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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

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

Defined in Optics.Internal.Indexed

Methods

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

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

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