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.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 function on all instances.

Minimal complete definition

fmapF

Methods

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

Instances

FunctorF k (Const (k -> *) x) Source # 

Methods

fmapF :: (forall (a :: Const (k -> *) x). f a -> g a) -> m f -> m g Source #

FunctorF k (Pair k a) Source # 

Methods

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

FunctorF k (MapF k ktp) Source # 

Methods

fmapF :: (forall (x :: MapF k ktp). f x -> g x) -> m f -> m 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 k (Const (k -> *) x) Source # 

Methods

foldMapF :: Monoid m => (forall (s :: Const (k -> *) x). e s -> m) -> t e -> m Source #

foldrF :: (forall (s :: Const (k -> *) x). e s -> b -> b) -> b -> t e -> b Source #

foldlF :: (forall (s :: Const (k -> *) x). b -> e s -> b) -> b -> t e -> b Source #

foldrF' :: (forall (s :: Const (k -> *) x). e s -> b -> b) -> b -> t e -> b Source #

foldlF' :: (forall (s :: Const (k -> *) x). b -> e s -> b) -> b -> t e -> b Source #

toListF :: (forall (tp :: Const (k -> *) x). f tp -> a) -> t f -> [a] Source #

FoldableF k (Pair k a) Source # 

Methods

foldMapF :: Monoid m => (forall (s :: Pair k a). e s -> m) -> t e -> m Source #

foldrF :: (forall (s :: Pair k a). e s -> b -> b) -> b -> t e -> b Source #

foldlF :: (forall (s :: Pair k a). b -> e s -> b) -> b -> t e -> b Source #

foldrF' :: (forall (s :: Pair k a). e s -> b -> b) -> b -> t e -> b Source #

foldlF' :: (forall (s :: Pair k a). b -> e s -> b) -> b -> t e -> b Source #

toListF :: (forall (tp :: Pair k a). f tp -> a) -> t f -> [a] Source #

FoldableF k (MapF k ktp) Source # 

Methods

foldMapF :: Monoid m => (forall (s :: MapF k ktp). e s -> m) -> t e -> m Source #

foldrF :: (forall (s :: MapF k ktp). e s -> b -> b) -> b -> t e -> b Source #

foldlF :: (forall (s :: MapF k ktp). b -> e s -> b) -> b -> t e -> b Source #

foldrF' :: (forall (s :: MapF k ktp). e s -> b -> b) -> b -> t e -> b Source #

foldlF' :: (forall (s :: MapF k ktp). b -> e s -> b) -> b -> t e -> b Source #

toListF :: (forall (tp :: MapF k ktp). f tp -> a) -> t 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 k (Const (k -> *) x) Source # 

Methods

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

TraversableF k (MapF k ktp) Source # 

Methods

traverseF :: Applicative m => (forall (s :: MapF k ktp). e s -> m (f s)) -> t e -> m (t 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.