parameterized-utils-1.0.1: 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.TraversableF

Description

This module declares classes for working with structures that accept a single parametric type parameter.

Synopsis

Documentation

class FunctorF m where Source #

A parameterized type that is a functor on all instances.

Minimal complete definition

fmapF

Methods

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

Instances
FunctorF (Const x :: (k -> *) -> *) Source # 
Instance details

Defined in Data.Parameterized.TraversableF

Methods

fmapF :: (forall (x0 :: k0). f x0 -> g x0) -> Const x f -> Const x g Source #

FunctorF (Pair a :: (k -> *) -> *) Source # 
Instance details

Defined in Data.Parameterized.Pair

Methods

fmapF :: (forall (x :: k0). f x -> g x) -> Pair a f -> Pair a g Source #

FunctorF (MapF ktp :: (k -> Type) -> *) Source # 
Instance details

Defined in Data.Parameterized.Map

Methods

fmapF :: (forall (x :: k0). f x -> g x) -> MapF ktp f -> MapF ktp g Source #

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

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

Minimal complete definition

foldMapF | foldrF

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 (Const x :: (k -> *) -> *) Source # 
Instance details

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 -> *) -> *) Source # 
Instance details

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) -> *) Source # 
Instance details

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 #

class (FunctorF t, FoldableF t) => TraversableF t where Source #

Minimal complete definition

traverseF

Methods

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

Instances
TraversableF (Const x :: (k -> *) -> *) Source # 
Instance details

Defined in Data.Parameterized.TraversableF

Methods

traverseF :: Applicative m => (forall (s :: k0). e s -> m (f s)) -> Const x e -> m (Const x f) Source #

TraversableF (MapF ktp :: (k -> Type) -> *) Source # 
Instance details

Defined in Data.Parameterized.Map

Methods

traverseF :: Applicative m => (forall (s :: k0). e s -> m (f s)) -> MapF ktp e -> m (MapF ktp f) Source #

traverseF_ :: (FoldableF t, Applicative f) => (forall s. e s -> f ()) -> t e -> f () Source #

Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results.

fmapFDefault :: TraversableF t => (forall s. e s -> f s) -> t e -> t f Source #

This function may be used as a value for fmapF in a FunctorF instance.

foldMapFDefault :: (TraversableF t, Monoid m) => (forall s. e s -> m) -> t e -> m Source #

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

allF :: FoldableF t => (forall tp. f tp -> Bool) -> t f -> Bool Source #

Return True if all values satisfy predicate.

anyF :: FoldableF t => (forall tp. f tp -> Bool) -> t f -> Bool Source #

Return True if any values satisfy predicate.