Copyright | (c) Galois Inc 2014-2015 |
---|---|
Maintainer | Joe Hendrix <jhendrix@galois.com> |
Safe Haskell | Trustworthy |
Language | Haskell98 |
Description : Traversing structures having a single parametric type followed by a fixed kind.
This module declares classes for working with structures that accept a parametric type parameter followed by some fixed kind.
Synopsis
- class TestEqualityFC (t :: (k -> *) -> l -> *) where
- testEqualityFC :: forall f. (forall x y. f x -> f y -> Maybe (x :~: y)) -> forall x y. t f x -> t f y -> Maybe (x :~: y)
- class TestEqualityFC t => OrdFC (t :: (k -> *) -> l -> *) where
- class ShowFC (t :: (k -> *) -> l -> *) where
- class HashableFC (t :: (k -> *) -> l -> *) where
- hashWithSaltFC :: forall f. (forall x. Int -> f x -> Int) -> forall x. Int -> t f x -> Int
- class FunctorFC (t :: (k -> *) -> l -> *) where
- fmapFC :: forall f g. (forall x. f x -> g x) -> forall x. t f x -> t g x
- class FoldableFC (t :: (k -> *) -> l -> *) where
- foldMapFC :: forall f m. Monoid m => (forall x. f x -> m) -> forall x. t f x -> m
- foldrFC :: forall f b. (forall x. f x -> b -> b) -> forall x. b -> t f x -> b
- foldlFC :: forall f b. (forall x. b -> f x -> b) -> forall x. b -> t f x -> b
- foldrFC' :: forall f b. (forall x. f x -> b -> b) -> forall x. b -> t f x -> b
- foldlFC' :: forall f b. (forall x. b -> f x -> b) -> forall x. b -> t f x -> b
- toListFC :: forall f a. (forall x. f x -> a) -> forall x. t f x -> [a]
- foldlMFC :: (FoldableFC t, Monad m) => (forall x. b -> f x -> m b) -> b -> t f c -> m b
- foldlMFC' :: (FoldableFC t, Monad m) => (forall x. b -> f x -> m b) -> b -> t f c -> m b
- foldrMFC :: (FoldableFC t, Monad m) => (forall x. f x -> b -> m b) -> b -> t f c -> m b
- foldrMFC' :: (FoldableFC t, Monad m) => (forall x. f x -> b -> m b) -> b -> t f c -> m b
- class (FunctorFC t, FoldableFC t) => TraversableFC (t :: (k -> *) -> l -> *) where
- traverseFC :: forall f g m. Applicative m => (forall x. f x -> m (g x)) -> forall x. t f x -> m (t g x)
- traverseFC_ :: (FoldableFC t, Applicative m) => (forall x. f x -> m a) -> forall x. t f x -> m ()
- forMFC_ :: (FoldableFC t, Applicative m) => t f c -> (forall x. f x -> m a) -> m ()
- forFC_ :: (FoldableFC t, Applicative m) => t f c -> (forall x. f x -> m a) -> m ()
- forFC :: (TraversableFC t, Applicative m) => t f x -> (forall y. f y -> m (g y)) -> m (t g x)
- fmapFCDefault :: TraversableFC t => forall f g. (forall x. f x -> g x) -> forall x. t f x -> t g x
- foldMapFCDefault :: (TraversableFC t, Monoid m) => (forall x. f x -> m) -> forall x. t f x -> m
- allFC :: FoldableFC t => (forall x. f x -> Bool) -> forall x. t f x -> Bool
- anyFC :: FoldableFC t => (forall x. f x -> Bool) -> forall x. t f x -> Bool
- lengthFC :: FoldableFC t => t f x -> Int
Documentation
class TestEqualityFC (t :: (k -> *) -> l -> *) where Source #
A parameterized class for types which can be tested for parameterized equality, when given an equality test for subterms.
testEqualityFC :: forall f. (forall x y. f x -> f y -> Maybe (x :~: y)) -> forall x y. t f x -> t f y -> Maybe (x :~: y) Source #
Instances
TestEqualityFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe testEqualityFC :: (forall (x :: k0) (y :: k0). f x -> f y -> Maybe (x :~: y)) -> forall (x :: l) (y :: l). Assignment f x -> Assignment f y -> Maybe (x :~: y) Source # |
class TestEqualityFC t => OrdFC (t :: (k -> *) -> l -> *) where Source #
A parameterized class for types which can be tested for parameterized ordering, when given an comparison test for subterms.
compareFC :: forall f. (forall x y. f x -> f y -> OrderingF x y) -> forall x y. t f x -> t f y -> OrderingF x y Source #
Instances
OrdFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe compareFC :: (forall (x :: k0) (y :: k0). f x -> f y -> OrderingF x y) -> forall (x :: l) (y :: l). Assignment f x -> Assignment f y -> OrderingF x y Source # |
class ShowFC (t :: (k -> *) -> l -> *) where Source #
A parameterized class for types which can be shown, when given functions to show parameterized subterms.
class HashableFC (t :: (k -> *) -> l -> *) where Source #
A parameterized class for types which can be hashed, when given functions to hash parameterized subterms.
class FunctorFC (t :: (k -> *) -> l -> *) where Source #
A parameterized type that is a function on all instances.
Instances
FunctorFC (List :: (k -> Type) -> [k] -> Type) Source # | |
FunctorFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe fmapFC :: (forall (x :: k0). f x -> g x) -> forall (x :: l). Assignment f x -> Assignment g x Source # |
class FoldableFC (t :: (k -> *) -> l -> *) where Source #
This is a generalization of the Foldable
class to
structures over parameterized terms.
foldMapFC :: forall f m. Monoid m => (forall x. f x -> m) -> forall x. t f x -> m Source #
Map each element of the structure to a monoid, and combine the results.
foldrFC :: forall f b. (forall x. f x -> b -> b) -> forall x. b -> t f x -> b Source #
Right-associative fold of a structure.
foldlFC :: forall f b. (forall x. b -> f x -> b) -> forall x. b -> t f x -> b Source #
Left-associative fold of a structure.
foldrFC' :: forall f b. (forall x. f x -> b -> b) -> forall x. b -> t f x -> b Source #
Right-associative fold of a structure, but with strict application of the operator.
foldlFC' :: forall f b. (forall x. b -> f x -> b) -> forall x. b -> t f x -> b Source #
Left-associative fold of a parameterized structure with a strict accumulator.
toListFC :: forall f a. (forall x. f x -> a) -> forall x. t f x -> [a] Source #
Convert structure to list.
Instances
FoldableFC (List :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.Parameterized.List foldMapFC :: Monoid m => (forall (x :: k0). f x -> m) -> forall (x :: l). List f x -> m Source # foldrFC :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> List f x -> b Source # foldlFC :: (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> List f x -> b Source # foldrFC' :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> List f x -> b Source # foldlFC' :: (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> List f x -> b Source # toListFC :: (forall (x :: k0). f x -> a) -> forall (x :: l). List f x -> [a] Source # | |
FoldableFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe foldMapFC :: Monoid m => (forall (x :: k0). f x -> m) -> forall (x :: l). Assignment f x -> m Source # foldrFC :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> Assignment f x -> b Source # foldlFC :: (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> Assignment f x -> b Source # foldrFC' :: (forall (x :: k0). f x -> b -> b) -> forall (x :: l). b -> Assignment f x -> b Source # foldlFC' :: (forall (x :: k0). b -> f x -> b) -> forall (x :: l). b -> Assignment f x -> b Source # toListFC :: (forall (x :: k0). f x -> a) -> forall (x :: l). Assignment f x -> [a] Source # |
foldlMFC :: (FoldableFC t, Monad m) => (forall x. b -> f x -> m b) -> b -> t f c -> m b Source #
Monadic fold over the elements of a structure from left to right.
foldlMFC' :: (FoldableFC t, Monad m) => (forall x. b -> f x -> m b) -> b -> t f c -> m b Source #
Monadic strict fold over the elements of a structure from left to right.
foldrMFC :: (FoldableFC t, Monad m) => (forall x. f x -> b -> m b) -> b -> t f c -> m b Source #
Monadic fold over the elements of a structure from right to left.
foldrMFC' :: (FoldableFC t, Monad m) => (forall x. f x -> b -> m b) -> b -> t f c -> m b Source #
Monadic strict fold over the elements of a structure from right to left.
class (FunctorFC t, FoldableFC t) => TraversableFC (t :: (k -> *) -> l -> *) where Source #
traverseFC :: forall f g m. Applicative m => (forall x. f x -> m (g x)) -> forall x. t f x -> m (t g x) Source #
Instances
TraversableFC (List :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.Parameterized.List traverseFC :: Applicative m => (forall (x :: k0). f x -> m (g x)) -> forall (x :: l). List f x -> m (List g x) Source # | |
TraversableFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # | |
Defined in Data.Parameterized.Context.Unsafe traverseFC :: Applicative m => (forall (x :: k0). f x -> m (g x)) -> forall (x :: l). Assignment f x -> m (Assignment g x) Source # |
traverseFC_ :: (FoldableFC t, Applicative m) => (forall x. f x -> m a) -> forall x. t f x -> m () Source #
Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results.
forMFC_ :: (FoldableFC t, Applicative m) => t f c -> (forall x. f x -> m a) -> m () Source #
Deprecated: Use forFC_
Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results.
forFC_ :: (FoldableFC t, Applicative m) => t f c -> (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.
forFC :: (TraversableFC t, Applicative m) => t f x -> (forall y. f y -> m (g y)) -> m (t g x) Source #
Flipped traverseFC
fmapFCDefault :: TraversableFC t => forall f g. (forall x. f x -> g x) -> forall x. t f x -> t g x Source #
This function may be used as a value for fmapF
in a FunctorF
instance.
foldMapFCDefault :: (TraversableFC t, Monoid m) => (forall x. f x -> m) -> forall x. t f x -> m Source #
allFC :: FoldableFC t => (forall x. f x -> Bool) -> forall x. t f x -> Bool Source #
Return True
if all values satisfy predicate.
anyFC :: FoldableFC t => (forall x. f x -> Bool) -> forall x. t f x -> Bool Source #
Return True
if any values satisfy predicate.
lengthFC :: FoldableFC t => t f x -> Int Source #
Return number of elements that we fold over.