| Copyright | (C) 2012-16 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | Rank2Types | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Control.Lens.Indexed
Contents
Description
(The classes in here need to be defined together for DefaultSignatures to work.)
Synopsis
- class Conjoined p => Indexable i p where- indexed :: p a b -> i -> a -> b
 
- class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p, Closed p) => Conjoined p where
- newtype Indexed i a b = Indexed {- runIndexed :: i -> a -> b
 
- (<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r
- (<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> r
- (.>) :: (st -> r) -> (kab -> st) -> kab -> r
- selfIndex :: Indexable a p => p a fb -> a -> fb
- reindexed :: Indexable j p => (i -> j) -> (Indexed i a b -> r) -> p a b -> r
- icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> r
- indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t
- indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f t
- class Functor f => FunctorWithIndex i f | f -> i where- imap :: (i -> a -> b) -> f a -> f b
- imapped :: IndexedSetter i (f a) (f b) a b
 
- class Foldable f => FoldableWithIndex i f | f -> i where
- iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- inone :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- none :: Foldable f => (a -> Bool) -> f a -> Bool
- 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 ()
- imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m ()
- iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m ()
- iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b]
- ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a)
- ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m b
- ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m b
- itoList :: FoldableWithIndex i f => f a -> [(i, a)]
- withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t)
- asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s)
- indices :: (Indexable i p, Applicative f) => (i -> Bool) -> Optical' p (Indexed i) f a a
- index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a a
- class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i t | t -> i where- itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b)
- itraversed :: IndexedTraversal i (t a) (t b) a b
 
- ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)
- imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b)
- iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b)
- imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
- imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
- ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> r
- ifoldMapByOf :: IndexedFold i t a -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> r
- itraverseBy :: TraversableWithIndex i t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> t a -> f (t b)
- itraverseByOf :: IndexedTraversal i s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> s -> f t
Indexing
class Conjoined p => Indexable i p where Source #
This class permits overloading of function application for things that also admit a notion of a key or index.
class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p, Closed p) => Conjoined p where Source #
This is a Profunctor that is both Corepresentable by f and Representable by g such
 that f is left adjoint to g. From this you can derive a lot of structure due
 to the preservation of limits and colimits.
Minimal complete definition
Nothing
Methods
distrib :: Functor f => p a b -> p (f a) (f b) Source #
Conjoined is strong enough to let us distribute every Conjoined
 Profunctor over every Haskell Functor. This is effectively a
 generalization of fmap.
conjoined :: (p ~ (->) => q (a -> b) r) -> q (p a b) r -> q (p a b) r Source #
This permits us to make a decision at an outermost point about whether or not we use an index.
Ideally any use of this function should be done in such a way so that you compute the same answer, but this cannot be enforced at the type level.
Instances
| Conjoined ReifiedGetter Source # | |
| Defined in Control.Lens.Reified Methods distrib :: Functor f => ReifiedGetter a b -> ReifiedGetter (f a) (f b) Source # conjoined :: ((ReifiedGetter ~ (->)) -> q (a -> b) r) -> q (ReifiedGetter a b) r -> q (ReifiedGetter a b) r Source # | |
| Conjoined (Indexed i) Source # | |
| Conjoined ((->) :: Type -> Type -> Type) Source # | |
newtype Indexed i a b Source #
A function with access to a index. This constructor may be useful when you need to store
 an Indexable in a container to avoid ImpredicativeTypes.
index :: Indexed i a b -> i -> a -> b
Constructors
| Indexed | |
| Fields 
 | |
Instances
(<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r infixr 9 Source #
Compose an Indexed function with a non-indexed function.
Mnemonically, the < points to the indexing we want to preserve.
>>>let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]>>>nestedMap^..(itraversed<.itraversed).withIndex[(1,"one,ten"),(1,"one,twenty"),(2,"two,thirty"),(2,"two,forty")]
(<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> r infixr 9 Source #
Composition of Indexed functions.
Mnemonically, the < and > points to the fact that we want to preserve the indices.
>>>let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]>>>nestedMap^..(itraversed<.>itraversed).withIndex[((1,10),"one,ten"),((1,20),"one,twenty"),((2,30),"two,thirty"),((2,40),"two,forty")]
(.>) :: (st -> r) -> (kab -> st) -> kab -> r infixr 9 Source #
Compose a non-indexed function with an Indexed function.
Mnemonically, the > points to the indexing we want to preserve.
This is the same as (..)
f  (and . gf ) gives you the index of .> gg unless g is index-preserving, like a
 Prism, Iso or Equality, in which case it'll pass through the index of f.
>>>let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]>>>nestedMap^..(itraversed.>itraversed).withIndex[(10,"one,ten"),(20,"one,twenty"),(30,"two,thirty"),(40,"two,forty")]
selfIndex :: Indexable a p => p a fb -> a -> fb Source #
Use a value itself as its own index. This is essentially an indexed version of id.
Note: When used to modify the value, this can break the index requirements assumed by indices and similar,
 so this is only properly an IndexedGetter, but it can be used as more.
selfIndex::IndexedGettera a b
reindexed :: Indexable j p => (i -> j) -> (Indexed i a b -> r) -> p a b -> r Source #
Remap the index.
icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> r Source #
Composition of Indexed functions with a user supplied function for combining indices.
indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t Source #
Transform a Traversal into an IndexedTraversal or
 a Fold into an IndexedFold, etc.
indexing::Traversals t a b ->IndexedTraversalInts t a bindexing::Prisms t a b ->IndexedTraversalInts t a bindexing::Lenss t a b ->IndexedLensInts t a bindexing::Isos t a b ->IndexedLensInts t a bindexing::Folds a ->IndexedFoldInts aindexing::Getters a ->IndexedGetterInts a
indexing::IndexableIntp =>LensLike(Indexingf) s t a b ->Overp f s t a b
indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f t Source #
Transform a Traversal into an IndexedTraversal or
 a Fold into an IndexedFold, etc.
This combinator is like indexing except that it handles large traversals and folds gracefully.
indexing64::Traversals t a b ->IndexedTraversalInt64s t a bindexing64::Prisms t a b ->IndexedTraversalInt64s t a bindexing64::Lenss t a b ->IndexedLensInt64s t a bindexing64::Isos t a b ->IndexedLensInt64s t a bindexing64::Folds a ->IndexedFoldInt64s aindexing64::Getters a ->IndexedGetterInt64s a
indexing64::IndexableInt64p =>LensLike(Indexing64f) s t a b ->Overp f s t a b
Indexed Functors
class Functor f => FunctorWithIndex i f | f -> i where Source #
A Functor with an additional index.
Instances must satisfy a modified form of the Functor laws:
imapf.imapg ≡imap(\i -> f i.g i)imap(\_ a -> a) ≡id
Minimal complete definition
Nothing
Methods
imap :: (i -> a -> b) -> f a -> f b Source #
Map with access to the index.
imap :: TraversableWithIndex i f => (i -> a -> b) -> f a -> f b Source #
Map with access to the index.
imapped :: IndexedSetter i (f a) (f b) a b Source #
The IndexedSetter for a FunctorWithIndex.
If you don't need access to the index, then mapped is more flexible in what it accepts.
Instances
Indexed Foldables
class Foldable f => FoldableWithIndex i f | f -> i where Source #
A container that supports folding with an additional index.
Minimal complete definition
Nothing
Methods
ifoldMap :: Monoid m => (i -> a -> m) -> f a -> m Source #
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 :: (TraversableWithIndex i f, Monoid m) => (i -> a -> m) -> f a -> m Source #
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
ifolded :: IndexedFold i (f a) a Source #
The IndexedFold of a FoldableWithIndex container.
ifolded . asIndexFoldableWithIndex.
>>>Data.Map.fromList [(2, "hello"), (1, "world")]^..ifolded.asIndex[1,2]
ifoldr :: (i -> a -> b -> b) -> b -> f a -> b Source #
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 Source #
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 [] Source # | |
| Defined in Control.Lens.Indexed | |
| FoldableWithIndex Int ZipList Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Int -> a -> m) -> ZipList a -> m Source # ifolded :: IndexedFold Int (ZipList a) a Source # ifoldr :: (Int -> a -> b -> b) -> b -> ZipList a -> b Source # ifoldl :: (Int -> b -> a -> b) -> b -> ZipList a -> b 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Int -> a -> m) -> NonEmpty a -> m Source # ifolded :: IndexedFold Int (NonEmpty a) a Source # ifoldr :: (Int -> a -> b -> b) -> b -> NonEmpty a -> b Source # ifoldl :: (Int -> b -> a -> b) -> b -> NonEmpty a -> b 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Int -> a -> m) -> IntMap a -> m Source # ifolded :: IndexedFold Int (IntMap a) a Source # ifoldr :: (Int -> a -> b -> b) -> b -> IntMap a -> b Source # ifoldl :: (Int -> b -> a -> b) -> b -> IntMap a -> b 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 # | |
| Defined in Control.Lens.Indexed | |
| FoldableWithIndex Int Vector Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Int -> a -> m) -> Vector a -> m Source # ifolded :: IndexedFold Int (Vector a) a Source # ifoldr :: (Int -> a -> b -> b) -> b -> Vector a -> b Source # ifoldl :: (Int -> b -> a -> b) -> b -> Vector a -> b Source # ifoldr' :: (Int -> a -> b -> b) -> b -> Vector a -> b Source # ifoldl' :: (Int -> b -> a -> b) -> b -> Vector a -> b Source # | |
| FoldableWithIndex Int Deque Source # | |
| Defined in Control.Lens.Internal.Deque Methods ifoldMap :: Monoid m => (Int -> a -> m) -> Deque a -> m Source # ifolded :: IndexedFold Int (Deque a) a Source # ifoldr :: (Int -> a -> b -> b) -> b -> Deque a -> b Source # ifoldl :: (Int -> b -> a -> b) -> b -> Deque a -> b Source # ifoldr' :: (Int -> a -> b -> b) -> b -> Deque a -> b Source # ifoldl' :: (Int -> b -> a -> b) -> b -> Deque a -> b Source # | |
| FoldableWithIndex () Maybe Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (() -> a -> m) -> Maybe a -> m Source # ifolded :: IndexedFold () (Maybe a) a Source # ifoldr :: (() -> a -> b -> b) -> b -> Maybe a -> b Source # ifoldl :: (() -> b -> a -> b) -> b -> Maybe a -> b Source # ifoldr' :: (() -> a -> b -> b) -> b -> Maybe a -> b Source # ifoldl' :: (() -> b -> a -> b) -> b -> Maybe a -> b Source # | |
| FoldableWithIndex () Par1 Source # | |
| Defined in Control.Lens.Indexed | |
| FoldableWithIndex () Identity Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (() -> a -> m) -> Identity a -> m Source # ifolded :: IndexedFold () (Identity a) a Source # ifoldr :: (() -> a -> b -> b) -> b -> Identity a -> b Source # ifoldl :: (() -> b -> a -> b) -> b -> Identity a -> b 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (i -> a -> m) -> Array i a -> m Source # ifolded :: IndexedFold i (Array i a) a Source # ifoldr :: (i -> a -> b -> b) -> b -> Array i a -> b Source # ifoldl :: (i -> b -> a -> b) -> b -> Array i a -> b Source # ifoldr' :: (i -> a -> b -> b) -> b -> Array i a -> b Source # ifoldl' :: (i -> b -> a -> b) -> b -> Array i a -> b Source # | |
| FoldableWithIndex i (Level i) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (i -> a -> m) -> Level i a -> m Source # ifolded :: IndexedFold i (Level i a) a Source # ifoldr :: (i -> a -> b -> b) -> b -> Level i a -> b Source # ifoldl :: (i -> b -> a -> b) -> b -> Level i a -> b Source # ifoldr' :: (i -> a -> b -> b) -> b -> Level i a -> b Source # ifoldl' :: (i -> b -> a -> b) -> b -> Level i a -> b Source # | |
| FoldableWithIndex k (HashMap k) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (k -> a -> m) -> HashMap k a -> m Source # ifolded :: IndexedFold k (HashMap k a) a Source # ifoldr :: (k -> a -> b -> b) -> b -> HashMap k a -> b Source # ifoldl :: (k -> b -> a -> b) -> b -> HashMap k a -> b Source # ifoldr' :: (k -> a -> b -> b) -> b -> HashMap k a -> b Source # ifoldl' :: (k -> b -> a -> b) -> b -> HashMap k a -> b Source # | |
| FoldableWithIndex k (Map k) Source # | |
| Defined in Control.Lens.Indexed | |
| FoldableWithIndex k ((,) k) Source # | |
| Defined in Control.Lens.Indexed | |
| FoldableWithIndex Void (V1 :: Type -> Type) Source # | |
| Defined in Control.Lens.Indexed | |
| FoldableWithIndex Void (U1 :: Type -> Type) Source # | |
| Defined in Control.Lens.Indexed | |
| FoldableWithIndex Void (Proxy :: Type -> Type) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Void -> a -> m) -> Proxy a -> m Source # ifolded :: IndexedFold Void (Proxy a) a Source # ifoldr :: (Void -> a -> b -> b) -> b -> Proxy a -> b Source # ifoldl :: (Void -> b -> a -> b) -> b -> Proxy a -> b Source # ifoldr' :: (Void -> a -> b -> b) -> b -> Proxy a -> b Source # ifoldl' :: (Void -> b -> a -> b) -> b -> Proxy a -> b Source # | |
| FoldableWithIndex () (Tagged a) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (() -> a0 -> m) -> Tagged a a0 -> m Source # ifolded :: IndexedFold () (Tagged a a0) a0 Source # ifoldr :: (() -> a0 -> b -> b) -> b -> Tagged a a0 -> b Source # ifoldl :: (() -> b -> a0 -> b) -> b -> Tagged a a0 -> b Source # ifoldr' :: (() -> a0 -> b -> b) -> b -> Tagged a a0 -> b Source # ifoldl' :: (() -> b -> a0 -> b) -> b -> Tagged a a0 -> b Source # | |
| FoldableWithIndex i f => FoldableWithIndex i (Rec1 f) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (i -> a -> m) -> Rec1 f a -> m Source # ifolded :: IndexedFold i (Rec1 f a) a Source # ifoldr :: (i -> a -> b -> b) -> b -> Rec1 f a -> b Source # ifoldl :: (i -> b -> a -> b) -> b -> Rec1 f a -> b 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m0 => (i -> a -> m0) -> IdentityT m a -> m0 Source # ifolded :: IndexedFold i (IdentityT m a) a Source # ifoldr :: (i -> a -> b -> b) -> b -> IdentityT m a -> b Source # ifoldl :: (i -> b -> a -> b) -> b -> IdentityT m a -> b 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (i -> a -> m) -> Reverse f a -> m Source # ifolded :: IndexedFold i (Reverse f a) a Source # ifoldr :: (i -> a -> b -> b) -> b -> Reverse f a -> b Source # ifoldl :: (i -> b -> a -> b) -> b -> Reverse f a -> b 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (i -> a -> m) -> Backwards f a -> m Source # ifolded :: IndexedFold i (Backwards f a) a Source # ifoldr :: (i -> a -> b -> b) -> b -> Backwards f a -> b Source # ifoldl :: (i -> b -> a -> b) -> b -> Backwards f a -> b Source # ifoldr' :: (i -> a -> b -> b) -> b -> Backwards f a -> b Source # ifoldl' :: (i -> b -> a -> b) -> b -> Backwards f a -> b Source # | |
| FoldableWithIndex i (Magma i t b) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (i -> a -> m) -> Magma i t b a -> m Source # ifolded :: IndexedFold i (Magma i t b a) a Source # ifoldr :: (i -> a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 Source # ifoldl :: (i -> b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 Source # ifoldr' :: (i -> a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 Source # ifoldl' :: (i -> b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 Source # | |
| FoldableWithIndex Void (K1 i c :: Type -> Type) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Void -> a -> m) -> K1 i c a -> m Source # ifolded :: IndexedFold Void (K1 i c a) a 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 # 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => ([Int] -> a -> m) -> Tree a -> m Source # ifolded :: IndexedFold [Int] (Tree a) a Source # ifoldr :: ([Int] -> a -> b -> b) -> b -> Tree a -> b Source # ifoldl :: ([Int] -> b -> a -> b) -> b -> Tree a -> b 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 [i] (Cofree f) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => ([i] -> a -> m) -> Cofree f a -> m Source # ifolded :: IndexedFold [i] (Cofree f a) a Source # ifoldr :: ([i] -> a -> b -> b) -> b -> Cofree f a -> b Source # ifoldl :: ([i] -> b -> a -> b) -> b -> Cofree f a -> b Source # ifoldr' :: ([i] -> a -> b -> b) -> b -> Cofree f a -> b Source # ifoldl' :: ([i] -> b -> a -> b) -> b -> Cofree f a -> b Source # | |
| FoldableWithIndex i f => FoldableWithIndex [i] (Free f) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => ([i] -> a -> m) -> Free f a -> m Source # ifolded :: IndexedFold [i] (Free f a) a Source # ifoldr :: ([i] -> a -> b -> b) -> b -> Free f a -> b Source # ifoldl :: ([i] -> b -> a -> b) -> b -> Free f a -> b Source # ifoldr' :: ([i] -> a -> b -> b) -> b -> Free f a -> b Source # ifoldl' :: ([i] -> b -> a -> b) -> b -> Free f a -> b Source # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :+: g) Source # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m Source # ifolded :: IndexedFold (Either i j) ((f :+: g) a) a 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 # 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m Source # ifolded :: IndexedFold (Either i j) ((f :*: g) a) a 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 # 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m Source # ifolded :: IndexedFold (Either i j) (Product f g a) a 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 # 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m Source # ifolded :: IndexedFold (Either i j) (Sum f g a) a 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 # 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => ((i, j) -> a -> m) -> (f :.: g) a -> m Source # ifolded :: IndexedFold (i, j) ((f :.: g) a) a 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 # 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 # | |
| Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => ((i, j) -> a -> m) -> Compose f g a -> m Source # ifolded :: IndexedFold (i, j) (Compose f g a) a 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 # 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 # | |
Indexed Foldable Combinators
itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f () Source #
ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f () Source #
imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m () Source #
Run monadic actions for each target of an IndexedFold or IndexedTraversal with access to the index,
 discarding the results.
When you don't need access to the index then mapMOf_ is more flexible in what it accepts.
mapM_≡imapM.const
iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m () Source #
Run monadic actions for each target of an IndexedFold or IndexedTraversal with access to the index,
 discarding the results (with the arguments flipped).
iforM_≡flipimapM_
When you don't need access to the index then forMOf_ is more flexible in what it accepts.
forMOf_l a ≡iforMOfl a.const
iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b] Source #
Concatenate the results of a function of the elements of an indexed container with access to the index.
When you don't need access to the index then concatMap is more flexible in what it accepts.
concatMap≡iconcatMap.consticoncatMap≡ifoldMap
ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m b Source #
ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m b Source #
itoList :: FoldableWithIndex i f => f a -> [(i, a)] Source #
Converting to Folds
withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t) Source #
Fold a container with indices returning both the indices and the values.
The result is only valid to compose in a Traversal, if you don't edit the
 index as edits to the index have no effect.
>>>[10, 20, 30] ^.. ifolded . withIndex[(0,10),(1,20),(2,30)]
>>>[10, 20, 30] ^.. ifolded . withIndex . alongside negated (re _Show)[(0,"10"),(-1,"20"),(-2,"30")]
asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s) Source #
When composed with an IndexedFold or IndexedTraversal this yields an
 (Indexed) Fold of the indices.
Restricting by Index
indices :: (Indexable i p, Applicative f) => (i -> Bool) -> Optical' p (Indexed i) f a a Source #
This allows you to filter an IndexedFold, IndexedGetter, IndexedTraversal or IndexedLens based on a predicate
 on the indices.
>>>["hello","the","world","!!!"]^..traversed.indices even["hello","world"]
>>>over (traversed.indices (>0)) Prelude.reverse $ ["He","was","stressed","o_O"]["He","saw","desserts","O_o"]
index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a a Source #
This allows you to filter an IndexedFold, IndexedGetter, IndexedTraversal or IndexedLens based on an index.
>>>["hello","the","world","!!!"]^?traversed.index 2Just "world"
Indexed Traversables
class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i t | t -> i where Source #
A Traversable with an additional index.
An instance must satisfy a (modified) form of the Traversable laws:
itraverse(constIdentity) ≡Identityfmap(itraversef).itraverseg ≡getCompose.itraverse(\i ->Compose.fmap(f i).g i)
Minimal complete definition
Nothing
Methods
itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b) Source #
Traverse an indexed container.
itraverse≡itraverseOfitraversed
itraverse :: (i ~ Int, Applicative f) => (i -> a -> f b) -> t a -> f (t b) Source #
Traverse an indexed container.
itraverse≡itraverseOfitraversed
itraversed :: IndexedTraversal i (t a) (t b) a b Source #
The IndexedTraversal of a TraversableWithIndex container.
Instances
Indexed Traversable Combinators
ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b) Source #
imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b) Source #
iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b) Source #
imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b) Source #
Generalizes mapAccumR to add access to the index.
imapAccumROf accumulates state from right to left.
mapAccumR≡imapAccumR.const
imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b) Source #
Generalizes mapAccumL to add access to the index.
imapAccumLOf accumulates state from left to right.
mapAccumLOf≡imapAccumL.const
Indexed Folds with Reified Monoid
ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> r Source #
ifoldMapByOf :: IndexedFold i t a -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> r Source #
Indexed Traversals with Reified Applicative
itraverseBy :: TraversableWithIndex i t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> t a -> f (t b) Source #
itraverseByOf :: IndexedTraversal i s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> s -> f t Source #