Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Indexed Foldables.
Synopsis
- 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)]
Indexed Foldables
class Foldable f => FoldableWithIndex i f | f -> i where Source #
A container that supports folding with an additional index.
Nothing
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
default ifoldMap :: (TraversableWithIndex i f, Monoid m) => (i -> a -> m) -> f a -> m Source #
ifoldMap' :: Monoid m => (i -> a -> m) -> f a -> m Source #
A variant of ifoldMap
that is strict in the accumulator.
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 -> 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 () Identity Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (() -> a -> m) -> Identity a -> m Source # 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 # ifoldr' :: (() -> a -> b -> b) -> b -> Identity a -> b Source # ifoldl' :: (() -> b -> a -> b) -> b -> Identity a -> b Source # | |
FoldableWithIndex () Par1 Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (() -> a -> m) -> Par1 a -> m Source # 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 () Maybe Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (() -> a -> m) -> Maybe a -> m Source # 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 # ifoldr' :: (() -> a -> b -> b) -> b -> Maybe a -> b Source # ifoldl' :: (() -> b -> a -> b) -> b -> Maybe a -> b Source # | |
FoldableWithIndex Int ZipList Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Int -> a -> m) -> ZipList a -> m Source # 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 # ifoldr' :: (Int -> a -> b -> b) -> b -> ZipList a -> b Source # ifoldl' :: (Int -> b -> a -> b) -> b -> ZipList a -> b Source # | |
FoldableWithIndex Int IntMap Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Int -> a -> m) -> IntMap a -> m Source # 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 # 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 WithIndex ifoldMap :: Monoid m => (Int -> a -> m) -> Seq a -> m Source # 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 Int NonEmpty Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Int -> a -> m) -> NonEmpty a -> m Source # 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 # ifoldr' :: (Int -> a -> b -> b) -> b -> NonEmpty a -> b Source # ifoldl' :: (Int -> b -> a -> b) -> b -> NonEmpty a -> b Source # | |
FoldableWithIndex Int [] Source # | |
Defined in WithIndex | |
FoldableWithIndex Void (Proxy :: Type -> Type) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Void -> a -> m) -> Proxy a -> m Source # 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 # ifoldr' :: (Void -> a -> b -> b) -> b -> Proxy a -> b Source # ifoldl' :: (Void -> b -> a -> b) -> b -> Proxy a -> b Source # | |
FoldableWithIndex Void (U1 :: Type -> Type) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Void -> a -> m) -> U1 a -> m Source # 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 (V1 :: Type -> Type) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Void -> a -> m) -> V1 a -> m Source # 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 # | |
Ix i => FoldableWithIndex i (Array i) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (i -> a -> m) -> Array i a -> m Source # 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 # 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 # | |
Defined in WithIndex ifoldMap :: Monoid m => (k -> a -> m) -> Map k a -> m Source # 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 # | |
Defined in WithIndex | |
FoldableWithIndex Void (Const e :: Type -> Type) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Void -> a -> m) -> Const e a -> m Source # ifoldMap' :: Monoid m => (Void -> a -> m) -> Const e a -> m Source # ifoldr :: (Void -> a -> b -> b) -> b -> Const e a -> b Source # ifoldl :: (Void -> b -> a -> b) -> b -> Const e a -> b Source # ifoldr' :: (Void -> a -> b -> b) -> b -> Const e a -> b Source # ifoldl' :: (Void -> b -> a -> b) -> b -> Const e a -> b Source # | |
FoldableWithIndex Void (Constant e :: Type -> Type) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Void -> a -> m) -> Constant e a -> m Source # ifoldMap' :: Monoid m => (Void -> a -> m) -> Constant e a -> m Source # ifoldr :: (Void -> a -> b -> b) -> b -> Constant e a -> b Source # ifoldl :: (Void -> b -> a -> b) -> b -> Constant e a -> b Source # ifoldr' :: (Void -> a -> b -> b) -> b -> Constant e a -> b Source # ifoldl' :: (Void -> b -> a -> b) -> b -> Constant e a -> b Source # | |
FoldableWithIndex i f => FoldableWithIndex i (Rec1 f) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (i -> a -> m) -> Rec1 f a -> m Source # 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 # ifoldr' :: (i -> a -> b -> b) -> b -> Rec1 f a -> b Source # ifoldl' :: (i -> b -> a -> b) -> b -> Rec1 f a -> b Source # | |
FoldableWithIndex i f => FoldableWithIndex i (Backwards f) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (i -> a -> m) -> Backwards f a -> m Source # 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 # ifoldr' :: (i -> a -> b -> b) -> b -> Backwards f a -> b Source # ifoldl' :: (i -> b -> a -> b) -> b -> Backwards f a -> b Source # | |
FoldableWithIndex i m => FoldableWithIndex i (IdentityT m) Source # | |
Defined in WithIndex ifoldMap :: Monoid m0 => (i -> a -> m0) -> IdentityT m a -> m0 Source # 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 # 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 WithIndex ifoldMap :: Monoid m => (i -> a -> m) -> Reverse f a -> m Source # 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 # ifoldr' :: (i -> a -> b -> b) -> b -> Reverse f a -> b Source # ifoldl' :: (i -> b -> a -> b) -> b -> Reverse f a -> b Source # | |
FoldableWithIndex Void (K1 i c :: Type -> Type) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Void -> a -> m) -> K1 i c a -> m Source # 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 # 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 WithIndex ifoldMap :: Monoid m => ([Int] -> a -> m) -> Tree a -> m Source # 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 # 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) (Product f g) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m Source # 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 # 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 WithIndex ifoldMap :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m Source # 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 # 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 (Either i j) (f :*: g) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m Source # 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 # 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 WithIndex ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m Source # 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 # 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 (i, j) (Compose f g) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => ((i, j) -> a -> m) -> Compose f g a -> m Source # 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 # 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 # | |
(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (f :.: g) Source # | |
Defined in WithIndex ifoldMap :: Monoid m => ((i, j) -> a -> m) -> (f :.: g) a -> m Source # 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 # ifoldr' :: ((i, j) -> a -> b -> b) -> b -> (f :.: g) a -> b Source # ifoldl' :: ((i, j) -> b -> a -> b) -> b -> (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 #
Traverse elements with access to the index i
, discarding the results (with the arguments flipped).
ifor_
≡flip
itraverse_
When you don't need access to the index then for_
is more flexible in what it accepts.
for_
a ≡ifor_
a.
const
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 #
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
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 #