parameterized-utils-2.1.4.0: Classes and data structures for working with data-kind indexed types
Copyright(c) Galois Inc 2014-2015
MaintainerJoe Hendrix <jhendrix@galois.com>
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Parameterized.TraversableFC

Description

This module declares classes for working with structures that accept a parametric type parameter followed by some fixed kind.

Synopsis

Documentation

class TestEqualityFC (t :: (k -> Type) -> l -> Type) where Source #

A parameterized class for types which can be tested for parameterized equality, when given an equality test for subterms.

Methods

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

Instances details
TestEqualityFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

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 -> Type) -> l -> Type) where Source #

A parameterized class for types which can be tested for parameterized ordering, when given an comparison test for subterms.

Methods

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

Instances details
OrdFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

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 -> Type) -> l -> Type) where Source #

A parameterized class for types which can be shown, when given functions to show parameterized subterms.

Minimal complete definition

showFC | showsPrecFC

Methods

showFC :: forall f. (forall x. f x -> String) -> forall x. t f x -> String Source #

showsPrecFC :: forall f. (forall x. Int -> f x -> ShowS) -> forall x. Int -> t f x -> ShowS Source #

class HashableFC (t :: (k -> Type) -> l -> Type) where Source #

A parameterized class for types which can be hashed, when given functions to hash parameterized subterms.

Methods

hashWithSaltFC :: forall f. (forall x. Int -> f x -> Int) -> forall x. Int -> t f x -> Int Source #

class FunctorFC (t :: (k -> Type) -> l -> Type) where Source #

A parameterized type that is a functor on all instances.

Laws:

Identity
fmapFC id == id
Composition
fmapFC (f . g) == fmapFC f . fmapFC g

Methods

fmapFC :: forall f g. (forall x. f x -> g x) -> forall x. t f x -> t g x Source #

Instances

Instances details
FunctorFC (List :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.Parameterized.List

Methods

fmapFC :: (forall (x :: k0). f x -> g x) -> forall (x :: l). List f x -> List g x Source #

FunctorFC (Assignment :: (k -> Type) -> Ctx k -> Type) Source # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

fmapFC :: (forall (x :: k0). f x -> g x) -> forall (x :: l). Assignment f x -> Assignment g x Source #

class FoldableFC (t :: (k -> Type) -> l -> Type) where Source #

This is a generalization of the Foldable class to structures over parameterized terms.

Minimal complete definition

foldMapFC | foldrFC

Methods

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

Instances details
FoldableFC (List :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.Parameterized.List

Methods

foldMapFC :: forall f m. 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 f b. (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 f b. (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 # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

foldMapFC :: forall f m. 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 f b. (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 f b. (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 -> Type) -> l -> Type) where Source #

Methods

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

Instances details
TraversableFC (List :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.Parameterized.List

Methods

traverseFC :: forall f g m. 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 # 
Instance details

Defined in Data.Parameterized.Context.Unsafe

Methods

traverseFC :: forall f g m. 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 #

This function may be used as a value for foldMap in a Foldable instance.

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.