parameterized-utils-1.0.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
LanguageHaskell98

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

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

Minimal complete definition

testEqualityFC

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

TestEqualityFC k (Ctx k) (Assignment k) Source # 

Methods

testEqualityFC :: (forall (x :: Assignment k) (y :: Assignment k). f x -> f y -> Maybe ((Assignment k :~: x) y)) -> forall (x :: l) (y :: l). t f x -> t f y -> Maybe ((l :~: x) y) Source #

TestEqualityFC k (Ctx k) (Assignment k) Source # 

Methods

testEqualityFC :: (forall (x :: Assignment k) (y :: Assignment k). f x -> f y -> Maybe ((Assignment k :~: x) y)) -> forall (x :: l) (y :: l). t f x -> t f y -> Maybe ((l :~: 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.

Minimal complete definition

compareFC

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

OrdFC k (Ctx k) (Assignment k) Source # 

Methods

compareFC :: (forall (x :: Assignment k) (y :: Assignment k). f x -> f y -> OrderingF (Assignment k) x y) -> forall (x :: l) (y :: l). t f x -> t f y -> OrderingF l x y Source #

OrdFC k (Ctx k) (Assignment k) Source # 

Methods

compareFC :: (forall (x :: Assignment k) (y :: Assignment k). f x -> f y -> OrderingF (Assignment k) x y) -> forall (x :: l) (y :: l). t f x -> t f y -> OrderingF l 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.

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

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

Minimal complete definition

hashWithSaltFC

Methods

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

class FunctorFC m where Source #

A parameterized type that is a function on all instances.

Minimal complete definition

fmapFC

Methods

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

Instances

FunctorFC k [k] (List k) Source # 

Methods

fmapFC :: (forall (x :: List k). f x -> g x) -> forall (x :: k). m f x -> m g x Source #

FunctorFC k (Ctx k) (Assignment k) Source # 

Methods

fmapFC :: (forall (x :: Assignment k). f x -> g x) -> forall (x :: k). m f x -> m g x Source #

FunctorFC k (Ctx k) (Assignment k) Source # 

Methods

fmapFC :: (forall (x :: Assignment k). f x -> g x) -> forall (x :: k). m f x -> m g x Source #

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

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

Minimal complete definition

foldMapFC | foldrFC

Methods

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.

Instances

FoldableFC k [k] (List k) Source # 

Methods

foldMapFC :: Monoid m => (forall (s :: List k). e s -> m) -> t e c -> m Source #

foldrFC :: (forall (s :: List k). e s -> b -> b) -> b -> t e c -> b Source #

foldlFC :: (forall (s :: List k). b -> e s -> b) -> b -> t e c -> b Source #

foldrFC' :: (forall (s :: List k). e s -> b -> b) -> b -> t e c -> b Source #

foldlFC' :: (forall (s :: List k). b -> e s -> b) -> b -> t e c -> b Source #

toListFC :: (forall (tp :: List k). f tp -> a) -> t f c -> [a] Source #

FoldableFC k (Ctx k) (Assignment k) Source # 

Methods

foldMapFC :: Monoid m => (forall (s :: Assignment k). e s -> m) -> t e c -> m Source #

foldrFC :: (forall (s :: Assignment k). e s -> b -> b) -> b -> t e c -> b Source #

foldlFC :: (forall (s :: Assignment k). b -> e s -> b) -> b -> t e c -> b Source #

foldrFC' :: (forall (s :: Assignment k). e s -> b -> b) -> b -> t e c -> b Source #

foldlFC' :: (forall (s :: Assignment k). b -> e s -> b) -> b -> t e c -> b Source #

toListFC :: (forall (tp :: Assignment k). f tp -> a) -> t f c -> [a] Source #

FoldableFC k (Ctx k) (Assignment k) Source # 

Methods

foldMapFC :: Monoid m => (forall (s :: Assignment k). e s -> m) -> t e c -> m Source #

foldrFC :: (forall (s :: Assignment k). e s -> b -> b) -> b -> t e c -> b Source #

foldlFC :: (forall (s :: Assignment k). b -> e s -> b) -> b -> t e c -> b Source #

foldrFC' :: (forall (s :: Assignment k). e s -> b -> b) -> b -> t e c -> b Source #

foldlFC' :: (forall (s :: Assignment k). b -> e s -> b) -> b -> t e c -> b Source #

toListFC :: (forall (tp :: Assignment k). f tp -> a) -> t f c -> [a] Source #

class (FunctorFC t, FoldableFC t) => TraversableFC t where Source #

Minimal complete definition

traverseFC

Methods

traverseFC :: Applicative m => (forall s. e s -> m (f s)) -> t e c -> m (t f c) Source #

Instances

TraversableFC k [k] (List k) Source # 

Methods

traverseFC :: Applicative m => (forall (s :: List k). e s -> m (f s)) -> t e c -> m (t f c) Source #

TraversableFC k (Ctx k) (Assignment k) Source # 

Methods

traverseFC :: Applicative m => (forall (s :: Assignment k). e s -> m (f s)) -> t e c -> m (t f c) Source #

TraversableFC k (Ctx k) (Assignment k) Source # 

Methods

traverseFC :: Applicative m => (forall (s :: Assignment k). e s -> m (f s)) -> t e c -> m (t f c) 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 #

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

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.