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 parametric type parameter followed by some fixed kind.
- class TestEqualityFC (t :: (k -> *) -> l -> *) where
- class TestEqualityFC t => OrdFC (t :: (k -> *) -> l -> *) where
- class ShowFC (t :: (k -> *) -> l -> *) where
- class HashableFC (t :: (k -> *) -> l -> *) where
- class FunctorFC m where
- class FoldableFC (t :: (k -> *) -> l -> *) where
- class (FunctorFC t, FoldableFC t) => TraversableFC t where
- traverseFC_ :: (FoldableFC t, Applicative f) => (forall s. e s -> f ()) -> t e c -> f ()
- forMFC_ :: (FoldableFC t, Applicative f) => t e c -> (forall s. e s -> f ()) -> f ()
- fmapFCDefault :: TraversableFC t => (forall s. e s -> f s) -> t e c -> t f c
- foldMapFCDefault :: (TraversableFC t, Monoid m) => (forall s. e s -> m) -> t e c -> m
- allFC :: FoldableFC t => (forall tp. f tp -> Bool) -> t f c -> Bool
- anyFC :: FoldableFC t => (forall tp. f tp -> Bool) -> t f c -> Bool
- lengthFC :: FoldableFC t => t e c -> 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 #
TestEqualityFC k (Ctx k) (Assignment k) Source # | |
TestEqualityFC k (Ctx k) (Assignment k) 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 #
OrdFC k (Ctx k) (Assignment k) Source # | |
OrdFC k (Ctx k) (Assignment k) 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 FoldableFC (t :: (k -> *) -> l -> *) where Source #
This is a generalization of the Foldable
class to
structures over parameterized terms.
foldMapFC :: Monoid m => (forall s. e s -> m) -> t e c -> m Source #
Map each element of the structure to a monoid, and combine the results.
foldrFC :: (forall s. e s -> b -> b) -> b -> t e c -> b Source #
Right-associative fold of a structure.
foldlFC :: (forall s. b -> e s -> b) -> b -> t e c -> b Source #
Left-associative fold of a structure.
foldrFC' :: (forall s. e s -> b -> b) -> b -> t e c -> b Source #
Right-associative fold of a structure, but with strict application of the operator.
foldlFC' :: (forall s. b -> e s -> b) -> b -> t e c -> b Source #
Left-associative fold of a parameterized structure with a strict accumulator.
toListFC :: (forall tp. f tp -> a) -> t f c -> [a] Source #
Convert structure to list.
FoldableFC k [k] (List k) Source # | |
FoldableFC k (Ctx k) (Assignment k) Source # | |
FoldableFC k (Ctx k) (Assignment k) Source # | |
class (FunctorFC t, FoldableFC t) => TraversableFC t where Source #
traverseFC :: Applicative m => (forall s. e s -> m (f s)) -> t e c -> m (t f c) Source #
TraversableFC k [k] (List k) Source # | |
TraversableFC k (Ctx k) (Assignment k) Source # | |
TraversableFC k (Ctx k) (Assignment k) Source # | |
traverseFC_ :: (FoldableFC t, Applicative f) => (forall s. e s -> f ()) -> t e c -> f () 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 f) => t e c -> (forall s. e s -> f ()) -> f () Source #
Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results.
fmapFCDefault :: TraversableFC t => (forall s. e s -> f s) -> t e c -> t f c Source #
This function may be used as a value for fmapF
in a FunctorF
instance.
foldMapFCDefault :: (TraversableFC t, Monoid m) => (forall s. e s -> m) -> t e c -> m Source #
allFC :: FoldableFC t => (forall tp. f tp -> Bool) -> t f c -> Bool Source #
Return True
if all values satisfy predicate.
anyFC :: FoldableFC t => (forall tp. f tp -> Bool) -> t f c -> Bool Source #
Return True
if any values satisfy predicate.
lengthFC :: FoldableFC t => t e c -> Int Source #
Return number of elements in list.