| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Ten.Foldable.WithIndex
Description
An extension of Foldable10 that provides access to some Index10.
Synopsis
- type family Index10 (f :: (k -> Type) -> Type) :: k -> Type
- class Foldable10 f => Foldable10WithIndex f where- ifoldMap10 :: Monoid w => (forall a. Index10 f a -> m a -> w) -> f m -> w
 
- ifoldl10 :: Foldable10WithIndex f => (forall a. Index10 f a -> b -> m a -> b) -> b -> f m -> b
- ifoldr10 :: Foldable10WithIndex f => (forall a. Index10 f a -> m a -> b -> b) -> b -> f m -> b
- itraverse10_ :: (Foldable10WithIndex f, Applicative g) => (forall a. Index10 f a -> m a -> g ()) -> f m -> g ()
- foldMap10C :: forall c f m w. (Entails (Index10 f) c, Foldable10WithIndex f, Monoid w) => (forall a. c a => m a -> w) -> f m -> w
- foldr10C :: forall c f m b. (Entails (Index10 f) c, Foldable10WithIndex f) => (forall a. c a => m a -> b -> b) -> b -> f m -> b
- foldl10C :: forall c f m b. (Entails (Index10 f) c, Foldable10WithIndex f) => (forall a. c a => b -> m a -> b) -> b -> f m -> b
- traverse10C_ :: forall c f g m. (Entails (Index10 f) c, Applicative g, Foldable10WithIndex f) => (forall a. c a => m a -> g ()) -> f m -> g ()
Documentation
type family Index10 (f :: (k -> Type) -> Type) :: k -> Type Source #
The index type associated with a given f.
This is often a GADT-like type, in that inspecting Index10 f a can refine
 a to some more concrete type, provide instances for it via Entails, etc.
Instances
| type Index10 (Wrapped1 (Representable10 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # | |
| Defined in Data.Ten.Representable type Index10 (Wrapped1 (Representable10 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) = Rep10 f | |
| type Index10 (g :.: f :: (k -> Type) -> Type) Source # | |
| type Index10 ((:**) k :: (Type -> Type) -> Type) Source # | |
class Foldable10 f => Foldable10WithIndex f where Source #
An extension of Foldable10 that provides access to some Index10.
Methods
ifoldMap10 :: Monoid w => (forall a. Index10 f a -> m a -> w) -> f m -> w Source #
Instances
| (Representable10 f, Foldable10 f) => Foldable10WithIndex (Wrapped1 (Representable10 :: ((k -> Type) -> Type) -> Constraint) f :: (k -> Type) -> Type) Source # | |
| Defined in Data.Ten.Representable Methods ifoldMap10 :: Monoid w => (forall (a :: k0). Index10 (Wrapped1 Representable10 f) a -> m a -> w) -> Wrapped1 Representable10 f m -> w Source # | |
| (Foldable g, Foldable10WithIndex f) => Foldable10WithIndex (g :.: f :: (k -> Type) -> Type) Source # | |
| Defined in Data.Ten.Foldable.WithIndex | |
| Foldable10WithIndex ((:**) k :: (Type -> Type) -> Type) Source # | |
| Defined in Data.Ten.Sigma | |
ifoldl10 :: Foldable10WithIndex f => (forall a. Index10 f a -> b -> m a -> b) -> b -> f m -> b Source #
foldl10 with an index parameter.
ifoldr10 :: Foldable10WithIndex f => (forall a. Index10 f a -> m a -> b -> b) -> b -> f m -> b Source #
foldr10 with an index parameter.
itraverse10_ :: (Foldable10WithIndex f, Applicative g) => (forall a. Index10 f a -> m a -> g ()) -> f m -> g () Source #
traverse10_ with an index parameter.
foldMap10C :: forall c f m w. (Entails (Index10 f) c, Foldable10WithIndex f, Monoid w) => (forall a. c a => m a -> w) -> f m -> w Source #
foldMap10 with an instance for every element.
foldr10C :: forall c f m b. (Entails (Index10 f) c, Foldable10WithIndex f) => (forall a. c a => m a -> b -> b) -> b -> f m -> b Source #
foldr10 with an instance for every element.
foldl10C :: forall c f m b. (Entails (Index10 f) c, Foldable10WithIndex f) => (forall a. c a => b -> m a -> b) -> b -> f m -> b Source #
foldl10 with an instance for every element.
traverse10C_ :: forall c f g m. (Entails (Index10 f) c, Applicative g, Foldable10WithIndex f) => (forall a. c a => m a -> g ()) -> f m -> g () Source #
traverse10_ with an instance for every element.