deep-transformations-0.2: Deep natural and unnatural tree transformations, including attribute grammars
Safe HaskellNone
LanguageHaskell2010

Transformation.Shallow

Description

Type classes Functor, Foldable, and Traversable that correspond to the standard type classes of the same name. The rank2classes package provides the equivalent set of classes for natural transformations. This module extends the functionality to unnatural transformations.

Synopsis

Documentation

class (Transformation t, Functor g) => Functor t g where Source #

Like Rank2.Functor except it takes a Transformation instead of a polymorphic function

Methods

(<$>) :: t -> g (Domain t) -> g (Codomain t) infixl 4 Source #

Instances

Instances details
(Functor t g, Functor t h) => Functor t (Product g h) Source # 
Instance details

Defined in Transformation.Shallow

Methods

(<$>) :: t -> Product g h (Domain t) -> Product g h (Codomain t) Source #

class (Transformation t, Foldable g) => Foldable t g where Source #

Like Rank2.Foldable except it takes a Transformation instead of a polymorphic function

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> g (Domain t) -> m Source #

Instances

Instances details
(Foldable t g, Foldable t h, Codomain t ~ (Const m :: Type -> Type), Monoid m) => Foldable t (Product g h) Source # 
Instance details

Defined in Transformation.Shallow

Methods

foldMap :: (Codomain t ~ Const m, Monoid m) => t -> Product g h (Domain t) -> m Source #

class (Transformation t, Traversable g) => Traversable t g where Source #

Like Rank2.Traversable except it takes a Transformation instead of a polymorphic function

Methods

traverse :: Codomain t ~ Compose m f => t -> g (Domain t) -> m (g f) Source #

Instances

Instances details
(Traversable t g, Traversable t h, Codomain t ~ Compose m f, Applicative m) => Traversable t (Product g h) Source # 
Instance details

Defined in Transformation.Shallow

Methods

traverse :: forall m (f :: Type -> Type). Codomain t ~ Compose m f => t -> Product g h (Domain t) -> m (Product g h f) Source #

fmap :: Functor t g => t -> g (Domain t) -> g (Codomain t) Source #

Alphabetical synonym for <$>