Copyright | (c) Galois Inc 2021 |
---|---|
Maintainer | Langston Barrett |
Safe Haskell | None |
Language | Haskell2010 |
As in the package indexed-traversable.
Synopsis
- class FunctorFC t => FunctorFCWithIndex (t :: (k -> Type) -> l -> Type) where
- class (FoldableFC t, FunctorFCWithIndex t) => FoldableFCWithIndex (t :: (k -> Type) -> l -> Type) where
- ifoldMapFC :: forall f m z. Monoid m => (forall x. IndexF (t f z) x -> f x -> m) -> t f z -> m
- ifoldrFC :: forall z f b. (forall x. IndexF (t f z) x -> f x -> b -> b) -> b -> t f z -> b
- ifoldlFC :: forall f b z. (forall x. IndexF (t f z) x -> b -> f x -> b) -> b -> t f z -> b
- ifoldrFC' :: forall f b z. (forall x. IndexF (t f z) x -> f x -> b -> b) -> b -> t f z -> b
- ifoldlFC' :: forall f b. (forall x. b -> f x -> b) -> forall x. b -> t f x -> b
- itoListFC :: forall f a z. (forall x. IndexF (t f z) x -> f x -> a) -> t f z -> [a]
- ifoldlMFC :: FoldableFCWithIndex t => Monad m => (forall x. IndexF (t f z) x -> b -> f x -> m b) -> b -> t f z -> m b
- ifoldrMFC :: FoldableFCWithIndex t => Monad m => (forall x. IndexF (t f z) x -> f x -> b -> m b) -> b -> t f z -> m b
- iallFC :: FoldableFCWithIndex t => (forall x. IndexF (t f z) x -> f x -> Bool) -> t f z -> Bool
- ianyFC :: FoldableFCWithIndex t => (forall x. IndexF (t f z) x -> f x -> Bool) -> t f z -> Bool
- class (TraversableFC t, FoldableFCWithIndex t) => TraversableFCWithIndex (t :: (k -> Type) -> l -> Type) where
- itraverseFC :: forall m z f g. Applicative m => (forall x. IndexF (t f z) x -> f x -> m (g x)) -> t f z -> m (t g z)
- imapFCDefault :: forall t f g z. TraversableFCWithIndex t => (forall x. IndexF (t f z) x -> f x -> g x) -> t f z -> t g z
- ifoldMapFCDefault :: forall t m z f. TraversableFCWithIndex t => Monoid m => (forall x. IndexF (t f z) x -> f x -> m) -> t f z -> m
Documentation
class FunctorFC t => FunctorFCWithIndex (t :: (k -> Type) -> l -> Type) where Source #
Instances
FunctorFCWithIndex (List :: (k -> Type) -> [k] -> Type) Source # | |
FunctorFCWithIndex (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe imapFC :: forall f g (z :: l). (forall (x :: k0). IndexF (Assignment f z) x -> f x -> g x) -> Assignment f z -> Assignment g z Source # |
class (FoldableFC t, FunctorFCWithIndex t) => FoldableFCWithIndex (t :: (k -> Type) -> l -> Type) where Source #
Nothing
ifoldMapFC :: forall f m z. Monoid m => (forall x. IndexF (t f z) x -> f x -> m) -> t f z -> m Source #
Like foldMapFC
, but with an index.
foldMapFC
f ≡ifoldMapFC
(const
f)
ifoldrFC :: forall z f b. (forall x. IndexF (t f z) x -> f x -> b -> b) -> b -> t f z -> b Source #
Like foldrFC
, but with an index.
ifoldlFC :: forall f b z. (forall x. IndexF (t f z) x -> b -> f x -> b) -> b -> t f z -> b Source #
Like foldlFC
, but with an index.
ifoldrFC' :: forall f b z. (forall x. IndexF (t f z) x -> f x -> b -> b) -> b -> t f z -> b Source #
Like ifoldrFC
, but with an index.
ifoldlFC' :: forall f b. (forall x. b -> f x -> b) -> forall x. b -> t f x -> b Source #
Like ifoldlFC
, but with an index.
itoListFC :: forall f a z. (forall x. IndexF (t f z) x -> f x -> a) -> t f z -> [a] Source #
Convert structure to list.
Instances
FoldableFCWithIndex (List :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.Parameterized.List ifoldMapFC :: forall f m (z :: l). Monoid m => (forall (x :: k0). IndexF (List f z) x -> f x -> m) -> List f z -> m Source # ifoldrFC :: forall (z :: l) f b. (forall (x :: k0). IndexF (List f z) x -> f x -> b -> b) -> b -> List f z -> b Source # ifoldlFC :: forall f b (z :: l). (forall (x :: k0). IndexF (List f z) x -> b -> f x -> b) -> b -> List f z -> b Source # ifoldrFC' :: forall f b (z :: l). (forall (x :: k0). IndexF (List f z) x -> f x -> b -> b) -> b -> List f z -> b Source # ifoldlFC' :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> List f x -> b Source # itoListFC :: forall f a (z :: l). (forall (x :: k0). IndexF (List f z) x -> f x -> a) -> List f z -> [a] Source # | |
FoldableFCWithIndex (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe ifoldMapFC :: forall f m (z :: l). Monoid m => (forall (x :: k0). IndexF (Assignment f z) x -> f x -> m) -> Assignment f z -> m Source # ifoldrFC :: forall (z :: l) f b. (forall (x :: k0). IndexF (Assignment f z) x -> f x -> b -> b) -> b -> Assignment f z -> b Source # ifoldlFC :: forall f b (z :: l). (forall (x :: k0). IndexF (Assignment f z) x -> b -> f x -> b) -> b -> Assignment f z -> b Source # ifoldrFC' :: forall f b (z :: l). (forall (x :: k0). IndexF (Assignment f z) x -> f x -> b -> b) -> b -> Assignment f z -> b Source # ifoldlFC' :: forall f b. (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> Assignment f x -> b Source # itoListFC :: forall f a (z :: l). (forall (x :: k0). IndexF (Assignment f z) x -> f x -> a) -> Assignment f z -> [a] Source # |
ifoldlMFC :: FoldableFCWithIndex t => Monad m => (forall x. IndexF (t f z) x -> b -> f x -> m b) -> b -> t f z -> m b Source #
Like foldlMFC
, but with an index.
ifoldrMFC :: FoldableFCWithIndex t => Monad m => (forall x. IndexF (t f z) x -> f x -> b -> m b) -> b -> t f z -> m b Source #
Like foldrMFC
, but with an index.
iallFC :: FoldableFCWithIndex t => (forall x. IndexF (t f z) x -> f x -> Bool) -> t f z -> Bool Source #
Like allFC
, but with an index.
ianyFC :: FoldableFCWithIndex t => (forall x. IndexF (t f z) x -> f x -> Bool) -> t f z -> Bool Source #
Like anyFC
, but with an index.
class (TraversableFC t, FoldableFCWithIndex t) => TraversableFCWithIndex (t :: (k -> Type) -> l -> Type) where Source #
itraverseFC :: forall m z f g. Applicative m => (forall x. IndexF (t f z) x -> f x -> m (g x)) -> t f z -> m (t g z) Source #
Like traverseFC
, but with an index.
traverseFC
f ≡itraverseFC
(const
f)
Instances
TraversableFCWithIndex (List :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.Parameterized.List itraverseFC :: forall m (z :: l) f g. Applicative m => (forall (x :: k0). IndexF (List f z) x -> f x -> m (g x)) -> List f z -> m (List g z) Source # | |
TraversableFCWithIndex (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe itraverseFC :: forall m (z :: l) f g. Applicative m => (forall (x :: k0). IndexF (Assignment f z) x -> f x -> m (g x)) -> Assignment f z -> m (Assignment g z) Source # |
imapFCDefault :: forall t f g z. TraversableFCWithIndex t => (forall x. IndexF (t f z) x -> f x -> g x) -> t f z -> t g z Source #
ifoldMapFCDefault :: forall t m z f. TraversableFCWithIndex t => Monoid m => (forall x. IndexF (t f z) x -> f x -> m) -> t f z -> m Source #