| Copyright | (c) Galois Inc 2014-2019 | 
|---|---|
| Maintainer | Joe Hendrix <jhendrix@galois.com> | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.Parameterized.TraversableF
Description
Description : Traversing structures having a single parametric type
This module declares classes for working with structures that accept a single parametric type parameter.
Synopsis
- class FunctorF m where- fmapF :: (forall x. f x -> g x) -> m f -> m g
 
- class FoldableF (t :: (k -> *) -> *) where- foldMapF :: Monoid m => (forall s. e s -> m) -> t e -> m
- foldrF :: (forall s. e s -> b -> b) -> b -> t e -> b
- foldlF :: (forall s. b -> e s -> b) -> b -> t e -> b
- foldrF' :: (forall s. e s -> b -> b) -> b -> t e -> b
- foldlF' :: (forall s. b -> e s -> b) -> b -> t e -> b
- toListF :: (forall tp. f tp -> a) -> t f -> [a]
 
- foldlMF :: (FoldableF t, Monad m) => (forall x. b -> f x -> m b) -> b -> t f -> m b
- foldlMF' :: (FoldableF t, Monad m) => (forall x. b -> f x -> m b) -> b -> t f -> m b
- foldrMF :: (FoldableF t, Monad m) => (forall x. f x -> b -> m b) -> b -> t f -> m b
- foldrMF' :: (FoldableF t, Monad m) => (forall x. f x -> b -> m b) -> b -> t f -> m b
- class (FunctorF t, FoldableF t) => TraversableF t where- traverseF :: Applicative m => (forall s. e s -> m (f s)) -> t e -> m (t f)
 
- traverseF_ :: (FoldableF t, Applicative f) => (forall s. e s -> f a) -> t e -> f ()
- forF_ :: (FoldableF t, Applicative m) => t f -> (forall x. f x -> m a) -> m ()
- forF :: (TraversableF t, Applicative m) => t e -> (forall s. e s -> m (f s)) -> m (t 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
- lengthF :: FoldableF t => t f -> Int
Documentation
class FunctorF m where Source #
A parameterized type that is a functor on all instances.
Instances
| FunctorF (Some :: (k -> Type) -> Type) Source # | |
| FunctorF (All :: (k -> Type) -> Type) Source # | |
| FunctorF (Const x :: (k -> Type) -> Type) Source # | |
| FunctorF (Pair a :: (k -> Type) -> Type) Source # | |
| FunctorF (MapF ktp :: (k -> Type) -> Type) Source # | |
| (FunctorF s, FunctorFC t) => FunctorF (Compose s t :: (l -> Type) -> Type) Source # | |
class FoldableF (t :: (k -> *) -> *) where Source #
This is a generalization of the Foldable class to
 structures over parameterized terms.
Methods
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 (Some :: (k -> Type) -> Type) Source # | |
| Defined in Data.Parameterized.Some Methods foldMapF :: Monoid m => (forall (s :: k0). e s -> m) -> Some e -> m Source # foldrF :: (forall (s :: k0). e s -> b -> b) -> b -> Some e -> b Source # foldlF :: (forall (s :: k0). b -> e s -> b) -> b -> Some e -> b Source # foldrF' :: (forall (s :: k0). e s -> b -> b) -> b -> Some e -> b Source # foldlF' :: (forall (s :: k0). b -> e s -> b) -> b -> Some e -> b Source # toListF :: (forall (tp :: k0). f tp -> a) -> Some f -> [a] Source # | |
| FoldableF (All :: (k -> Type) -> Type) Source # | |
| Defined in Data.Parameterized.All Methods foldMapF :: Monoid m => (forall (s :: k0). e s -> m) -> All e -> m Source # foldrF :: (forall (s :: k0). e s -> b -> b) -> b -> All e -> b Source # foldlF :: (forall (s :: k0). b -> e s -> b) -> b -> All e -> b Source # foldrF' :: (forall (s :: k0). e s -> b -> b) -> b -> All e -> b Source # foldlF' :: (forall (s :: k0). b -> e s -> b) -> b -> All e -> b Source # toListF :: (forall (tp :: k0). f tp -> a) -> All f -> [a] Source # | |
| FoldableF (Const x :: (k -> Type) -> Type) Source # | |
| Defined in Data.Parameterized.TraversableF Methods 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 -> Type) -> Type) Source # | |
| Defined in Data.Parameterized.Pair Methods 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) -> Type) Source # | |
| Defined in Data.Parameterized.Map Methods 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 # | |
| (TraversableF s, TraversableFC t) => FoldableF (Compose s t :: (l -> Type) -> Type) Source # | |
| Defined in Data.Parameterized.TraversableF Methods foldMapF :: Monoid m => (forall (s0 :: k). e s0 -> m) -> Compose s t e -> m Source # foldrF :: (forall (s0 :: k). e s0 -> b -> b) -> b -> Compose s t e -> b Source # foldlF :: (forall (s0 :: k). b -> e s0 -> b) -> b -> Compose s t e -> b Source # foldrF' :: (forall (s0 :: k). e s0 -> b -> b) -> b -> Compose s t e -> b Source # foldlF' :: (forall (s0 :: k). b -> e s0 -> b) -> b -> Compose s t e -> b Source # toListF :: (forall (tp :: k). f tp -> a) -> Compose s t f -> [a] Source # | |
foldlMF :: (FoldableF t, Monad m) => (forall x. b -> f x -> m b) -> b -> t f -> m b Source #
Monadic fold over the elements of a structure from left to right.
foldlMF' :: (FoldableF t, Monad m) => (forall x. b -> f x -> m b) -> b -> t f -> m b Source #
Monadic strict fold over the elements of a structure from left to right.
foldrMF :: (FoldableF t, Monad m) => (forall x. f x -> b -> m b) -> b -> t f -> m b Source #
Monadic fold over the elements of a structure from right to left.
foldrMF' :: (FoldableF t, Monad m) => (forall x. f x -> b -> m b) -> b -> t f -> m b Source #
Monadic strict fold over the elements of a structure from right to left.
class (FunctorF t, FoldableF t) => TraversableF t where Source #
Methods
traverseF :: Applicative m => (forall s. e s -> m (f s)) -> t e -> m (t f) Source #
Instances
| TraversableF (Some :: (k -> Type) -> Type) Source # | |
| Defined in Data.Parameterized.Some | |
| TraversableF (Const x :: (k -> Type) -> Type) Source # | |
| Defined in Data.Parameterized.TraversableF | |
| TraversableF (MapF ktp :: (k -> Type) -> Type) Source # | |
| Defined in Data.Parameterized.Map | |
| (TraversableF s, TraversableFC t) => TraversableF (Compose s t :: (l -> Type) -> Type) Source # | Traverse twice over: go under the  | 
| Defined in Data.Parameterized.TraversableF | |
traverseF_ :: (FoldableF t, Applicative f) => (forall s. e s -> f a) -> t e -> f () Source #
Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results.
forF_ :: (FoldableF t, Applicative m) => t f -> (forall x. f x -> m a) -> m () Source #
Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results.
forF :: (TraversableF t, Applicative m) => t e -> (forall s. e s -> m (f s)) -> m (t f) Source #
Flipped traverseF
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 #
allF :: FoldableF t => (forall tp. f tp -> Bool) -> t f -> Bool Source #
Return True if all values satisfy the predicate.