| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Optics.IxFold
Description
Synopsis
- type IxFold i s a = Optic' A_Fold (WithIx i) s a
- ifoldVL :: (forall f. Applicative f => (i -> a -> f u) -> s -> f v) -> IxFold i s a
- ifoldMapOf :: (Is k A_Fold, Monoid m, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> m) -> s -> m
- ifoldrOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> r -> r) -> r -> s -> r
- ifoldlOf' :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> r -> a -> r) -> r -> s -> r
- itoListOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> s -> [(i, a)]
- itraverseOf_ :: (Is k A_Fold, Applicative f, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> f r) -> s -> f ()
- iforOf_ :: (Is k A_Fold, Applicative f, is `HasSingleIndex` 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. Applicative f => (i -> a -> f u -> f u) -> f v -> s -> f w) -> IxFold i s a
- iheadOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> s -> Maybe (i, a)
- ilastOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> s -> Maybe (i, a)
- ianyOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
- iallOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
- inoneOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
- ifindOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Maybe (i, a)
- ifindMOf :: (Is k A_Fold, Monad m, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> m Bool) -> s -> m (Maybe (i, a))
- ipre :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> IxAffineFold i s a
- ifiltered :: (Is k A_Fold, is `HasSingleIndex` i) => (i -> a -> Bool) -> Optic' k is s a -> IxFold i s a
- ibackwards_ :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> IxFold i s a
- 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
- 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
- data A_Fold :: OpticKind
- class Foldable f => FoldableWithIndex i (f :: Type -> Type) | f -> i where
Formation
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_≡iditraverseOf_.ifoldVL≡id
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 #
Additional elimination forms
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 #
iallOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool Source #
inoneOf :: (Is k A_Fold, is `HasSingleIndex` i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool Source #
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.
For the traversal version see isingular.
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.
Monoid structures
IxFold admits (at least) two monoid structures:
- isummingconcatenates results from both folds.
- ifailingreturns results from the second fold only if the first returns no results.
In both cases, the identity element of the monoid is
 ignored, which returns no results.
There is no Semigroup or Monoid instance for IxFold, because there is
 not a unique choice of monoid to use, and the (<>) operator could not be
 used to combine optics of different kinds.
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 #
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.
>>>itoListOf (_1 % ifolded `ifailing` _2 % ifolded) (["a"], ["b","c"])[(0,"a")]>>>itoListOf (_1 % ifolded `ifailing` _2 % ifolded) ([], ["b","c"])[(0,"b"),(1,"c")]
Subtyping
data A_Fold :: OpticKind Source #
Tag for a fold.
Instances
Re-exports
class Foldable f => FoldableWithIndex i (f :: Type -> Type) | f -> i where #
A container that supports folding with an additional index.
Minimal complete definition
Nothing
Methods
ifoldMap :: Monoid m => (i -> a -> m) -> f a -> m #
Fold a container by mapping value to an arbitrary Monoid with access to the index i.
When you don't need access to the index then foldMap is more flexible in what it accepts.
foldMap≡ifoldMap.const
ifoldMap' :: Monoid m => (i -> a -> m) -> f a -> m #
A variant of ifoldMap that is strict in the accumulator.
ifoldr :: (i -> a -> b -> b) -> b -> f a -> b #
Right-associative fold of an indexed container with access to the index i.
When you don't need access to the index then foldr is more flexible in what it accepts.
foldr≡ifoldr.const
ifoldl :: (i -> b -> a -> b) -> b -> f a -> b #
Left-associative fold of an indexed container with access to the index i.
When you don't need access to the index then foldl is more flexible in what it accepts.
foldl≡ifoldl.const
Instances
| FoldableWithIndex Int [] | |
| FoldableWithIndex Int ZipList | |
| Defined in WithIndex | |
| FoldableWithIndex Int NonEmpty | |
| Defined in WithIndex | |
| FoldableWithIndex Int IntMap | |
| Defined in WithIndex | |
| FoldableWithIndex Int Seq | |
| FoldableWithIndex () Maybe | |
| FoldableWithIndex () Par1 | |
| FoldableWithIndex () Identity | |
| Defined in WithIndex | |
| FoldableWithIndex k (Map k) | |
| FoldableWithIndex k ((,) k) | |
| Ix i => FoldableWithIndex i (Array i) | |
| Defined in WithIndex | |
| FoldableWithIndex Void (V1 :: Type -> Type) | |
| FoldableWithIndex Void (U1 :: Type -> Type) | |
| FoldableWithIndex Void (Proxy :: Type -> Type) | |
| Defined in WithIndex | |
| FoldableWithIndex i f => FoldableWithIndex i (Reverse f) | |
| Defined in WithIndex | |
| FoldableWithIndex i f => FoldableWithIndex i (Rec1 f) | |
| FoldableWithIndex i m => FoldableWithIndex i (IdentityT m) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m0 => (i -> a -> m0) -> IdentityT m a -> m0 # ifoldMap' :: Monoid m0 => (i -> a -> m0) -> IdentityT m a -> m0 # ifoldr :: (i -> a -> b -> b) -> b -> IdentityT m a -> b # ifoldl :: (i -> b -> a -> b) -> b -> IdentityT m a -> b # | |
| FoldableWithIndex i f => FoldableWithIndex i (Backwards f) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m => (i -> a -> m) -> Backwards f a -> m # ifoldMap' :: Monoid m => (i -> a -> m) -> Backwards f a -> m # ifoldr :: (i -> a -> b -> b) -> b -> Backwards f a -> b # ifoldl :: (i -> b -> a -> b) -> b -> Backwards f a -> b # | |
| FoldableWithIndex Void (Const e :: Type -> Type) | |
| Defined in WithIndex | |
| FoldableWithIndex Void (Constant e :: Type -> Type) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m => (Void -> a -> m) -> Constant e a -> m # ifoldMap' :: Monoid m => (Void -> a -> m) -> Constant e a -> m # ifoldr :: (Void -> a -> b -> b) -> b -> Constant e a -> b # ifoldl :: (Void -> b -> a -> b) -> b -> Constant e a -> b # ifoldr' :: (Void -> a -> b -> b) -> b -> Constant e a -> b # ifoldl' :: (Void -> b -> a -> b) -> b -> Constant e a -> b # | |
| FoldableWithIndex Void (K1 i c :: Type -> Type) | |
| Defined in WithIndex | |
| FoldableWithIndex [Int] Tree | |
| Defined in WithIndex | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Sum f g) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m # ifoldMap' :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m # ifoldr :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b # ifoldl :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b # ifoldr' :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b # ifoldl' :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Product f g) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m # ifoldMap' :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m # ifoldr :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b # ifoldl :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b # ifoldr' :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b # ifoldl' :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :+: g) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m # ifoldMap' :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m # ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b # ifoldl :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b # ifoldr' :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b # ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :*: g) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m # ifoldMap' :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m # ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b # ifoldl :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b # ifoldr' :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b # ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (Compose f g) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m => ((i, j) -> a -> m) -> Compose f g a -> m # ifoldMap' :: Monoid m => ((i, j) -> a -> m) -> Compose f g a -> m # ifoldr :: ((i, j) -> a -> b -> b) -> b -> Compose f g a -> b # ifoldl :: ((i, j) -> b -> a -> b) -> b -> Compose f g a -> b # ifoldr' :: ((i, j) -> a -> b -> b) -> b -> Compose f g a -> b # ifoldl' :: ((i, j) -> b -> a -> b) -> b -> Compose f g a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (f :.: g) | |
| Defined in WithIndex Methods ifoldMap :: Monoid m => ((i, j) -> a -> m) -> (f :.: g) a -> m # ifoldMap' :: Monoid m => ((i, j) -> a -> m) -> (f :.: g) a -> m # ifoldr :: ((i, j) -> a -> b -> b) -> b -> (f :.: g) a -> b # ifoldl :: ((i, j) -> b -> a -> b) -> b -> (f :.: g) a -> b # ifoldr' :: ((i, j) -> a -> b -> b) -> b -> (f :.: g) a -> b # ifoldl' :: ((i, j) -> b -> a -> b) -> b -> (f :.: g) a -> b # | |