Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
(These need to be defined together for DefaultSignatures
to work.)
- class Functor f => FunctorWithIndex i f | f -> i where
- imap :: (i -> a -> b) -> f a -> f b
- imapped :: FunctorWithIndex i f => IndexedSetter i (f a) (f b) a b
- class Foldable f => FoldableWithIndex i f | f -> i where
- ifolded :: FoldableWithIndex i f => IndexedFold i (f a) a
- ifolding :: FoldableWithIndex i f => (s -> f a) -> IndexedFold i s a
- iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- iall :: FoldableWithIndex i f => (i -> 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)]
- withIndices :: FoldableWithIndex i f => Fold (f a) (i, a)
- indices :: FoldableWithIndex i f => Fold (f a) i
- 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 :: TraversableWithIndex i f => IndexedTraversal i (f a) (f 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)
- iwhere :: TraversableWithIndex i t => (i -> Bool) -> SimpleIndexedTraversal i (t a) a
Indexed Functors
class Functor f => FunctorWithIndex i f | f -> i whereSource
A Functor
with an additional index.
Instances must satisfy a modified form of the Functor
laws:
imap
f.
imap
g ≡imap
(i -> f i . g i)imap
(_ a -> a) ≡id
FunctorWithIndex Int [] | The position in the list is available as the index. |
FunctorWithIndex Int Seq | The position in the sequence is available as the index. |
FunctorWithIndex Int IntMap | |
FunctorWithIndex Int Vector | |
(Eq k, Hashable k) => FunctorWithIndex k (HashMap k) | |
FunctorWithIndex k (Map k) |
imapped :: FunctorWithIndex i f => IndexedSetter i (f a) (f b) a bSource
The IndexedSetter
for a FunctorWithIndex
.
If you don't need access to the index, then mapped
is more flexible in what it accepts.
Indexed Foldables
class Foldable f => FoldableWithIndex i f | f -> i whereSource
A container that supports folding with an additional index.
ifoldMap :: Monoid m => (i -> a -> m) -> f a -> mSource
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
ifoldr :: (i -> a -> b -> b) -> b -> f a -> bSource
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 -> bSource
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
FoldableWithIndex Int [] | |
FoldableWithIndex Int Seq | |
FoldableWithIndex Int IntMap | |
FoldableWithIndex Int Vector | |
(Eq k, Hashable k) => FoldableWithIndex k (HashMap k) | |
FoldableWithIndex k (Map k) |
ifolded :: FoldableWithIndex i f => IndexedFold i (f a) aSource
The IndexedFold
of a FoldableWithIndex
container.
ifolding :: FoldableWithIndex i f => (s -> f a) -> IndexedFold i s aSource
Indexed Foldable Combinators
iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> BoolSource
iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> BoolSource
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_
≡flip
imapM_
When you don't need access to the index then forMOf_
is more flexible in what it accepts.
forMOf_
l a ≡iforMOf
l 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
.const
iconcatMap
≡ifoldMap
ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a)Source
ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m bSource
ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m bSource
itoList :: FoldableWithIndex i f => f a -> [(i, a)]Source
Converting to Folds
withIndices :: FoldableWithIndex i f => Fold (f a) (i, a)Source
Fold a container with indices returning both the indices and the values.
indices :: FoldableWithIndex i f => Fold (f a) iSource
Fold a container with indices returning only the indices.
Indexed Traversables
class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i t | t -> i whereSource
A Traversable
with an additional index.
An instance must satisfy a (modified) form of the Traversable
laws:
itraverse
(const
Identity
) ≡Identity
fmap
(itraverse
f).
itraverse
g ≡getCompose
.
itraverse
(i ->Compose
.
fmap
(f i).
g i)
itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b)Source
Traverse an indexed container.
itraversed :: TraversableWithIndex i f => IndexedTraversal i (f a) (f b) a bSource
The IndexedTraversal
of a TraversableWithIndex
container.
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
iwhere :: TraversableWithIndex i t => (i -> Bool) -> SimpleIndexedTraversal i (t a) aSource
Access the element of an indexed container where the index matches a predicate.
>>>
over (iwhere (>0)) Prelude.reverse $ ["He","was","stressed","o_O"]
["He","saw","desserts","O_o"]