Copyright | (c) Galois Inc 2014-2015 |
---|---|
Maintainer | Joe Hendrix <jhendrix@galois.com> |
Safe Haskell | Trustworthy |
Language | Haskell98 |
This module declares classes for working with structures that accept a single parametric type parameter.
Synopsis
- class FunctorF m where
- class FoldableF (t :: (k -> *) -> *) where
- class (FunctorF t, FoldableF t) => TraversableF t where
- traverseF_ :: (FoldableF t, Applicative f) => (forall s. e s -> f ()) -> t e -> f ()
- fmapFDefault :: TraversableF t => (forall s. e s -> f s) -> t e -> t f
- foldMapFDefault :: (TraversableF t, Monoid m) => (forall s. e s -> m) -> t e -> m
- allF :: FoldableF t => (forall tp. f tp -> Bool) -> t f -> Bool
- anyF :: FoldableF t => (forall tp. f tp -> Bool) -> t f -> Bool
Documentation
class FunctorF m where Source #
A parameterized type that is a functor on all instances.
class FoldableF (t :: (k -> *) -> *) where Source #
This is a generalization of the Foldable
class to
structures over parameterized terms.
foldMapF :: Monoid m => (forall s. e s -> m) -> t e -> m Source #
Map each element of the structure to a monoid, and combine the results.
foldrF :: (forall s. e s -> b -> b) -> b -> t e -> b Source #
Right-associative fold of a structure.
foldlF :: (forall s. b -> e s -> b) -> b -> t e -> b Source #
Left-associative fold of a structure.
foldrF' :: (forall s. e s -> b -> b) -> b -> t e -> b Source #
Right-associative fold of a structure, but with strict application of the operator.
foldlF' :: (forall s. b -> e s -> b) -> b -> t e -> b Source #
Left-associative fold of a parameterized structure with a strict accumulator.
toListF :: (forall tp. f tp -> a) -> t f -> [a] Source #
Convert structure to list.
Instances
FoldableF (Const x :: (k -> *) -> *) Source # | |
Defined in Data.Parameterized.TraversableF foldMapF :: Monoid m => (forall (s :: k0). e s -> m) -> Const x e -> m Source # foldrF :: (forall (s :: k0). e s -> b -> b) -> b -> Const x e -> b Source # foldlF :: (forall (s :: k0). b -> e s -> b) -> b -> Const x e -> b Source # foldrF' :: (forall (s :: k0). e s -> b -> b) -> b -> Const x e -> b Source # foldlF' :: (forall (s :: k0). b -> e s -> b) -> b -> Const x e -> b Source # toListF :: (forall (tp :: k0). f tp -> a) -> Const x f -> [a] Source # | |
FoldableF (Pair a :: (k -> *) -> *) Source # | |
Defined in Data.Parameterized.Pair foldMapF :: Monoid m => (forall (s :: k0). e s -> m) -> Pair a e -> m Source # foldrF :: (forall (s :: k0). e s -> b -> b) -> b -> Pair a e -> b Source # foldlF :: (forall (s :: k0). b -> e s -> b) -> b -> Pair a e -> b Source # foldrF' :: (forall (s :: k0). e s -> b -> b) -> b -> Pair a e -> b Source # foldlF' :: (forall (s :: k0). b -> e s -> b) -> b -> Pair a e -> b Source # toListF :: (forall (tp :: k0). f tp -> a0) -> Pair a f -> [a0] Source # | |
FoldableF (MapF ktp :: (k -> Type) -> *) Source # | |
Defined in Data.Parameterized.Map foldMapF :: Monoid m => (forall (s :: k0). e s -> m) -> MapF ktp e -> m Source # foldrF :: (forall (s :: k0). e s -> b -> b) -> b -> MapF ktp e -> b Source # foldlF :: (forall (s :: k0). b -> e s -> b) -> b -> MapF ktp e -> b Source # foldrF' :: (forall (s :: k0). e s -> b -> b) -> b -> MapF ktp e -> b Source # foldlF' :: (forall (s :: k0). b -> e s -> b) -> b -> MapF ktp e -> b Source # toListF :: (forall (tp :: k0). f tp -> a) -> MapF ktp f -> [a] Source # |
class (FunctorF t, FoldableF t) => TraversableF t where Source #
traverseF :: Applicative m => (forall s. e s -> m (f s)) -> t e -> m (t f) Source #
Instances
TraversableF (Const x :: (k -> *) -> *) Source # | |
Defined in Data.Parameterized.TraversableF | |
TraversableF (MapF ktp :: (k -> Type) -> *) Source # | |
Defined in Data.Parameterized.Map |
traverseF_ :: (FoldableF t, Applicative f) => (forall s. e s -> f ()) -> t e -> f () Source #
Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results.
fmapFDefault :: TraversableF t => (forall s. e s -> f s) -> t e -> t f Source #
foldMapFDefault :: (TraversableF t, Monoid m) => (forall s. e s -> m) -> t e -> m Source #