natural-transformation-0.4: A natural transformation package.

Copyright(C) 2015 The University of Kansas
LicenseBSD-style (see the file LICENSE)
MaintainerAndy Gill
StabilityExperimental
Safe HaskellSafe
LanguageHaskell2010

Control.Natural

Contents

Description

A data type and class for natural transformations.

Synopsis

Newtype for a Natural Transformation

newtype f :~> g infixr 0 Source #

A natural transformation suitable for storing in a container.

Constructors

NT 

Fields

Instances

Transformation k f g ((:~>) k f g) Source # 

Methods

(#) :: t -> forall a. g a -> (k :~> f) g a Source #

Category (k -> *) ((:~>) k) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

(~) (k -> *) f g => Semigroup ((:~>) k f g) Source # 

Methods

(<>) :: (k :~> f) g -> (k :~> f) g -> (k :~> f) g #

sconcat :: NonEmpty ((k :~> f) g) -> (k :~> f) g #

stimes :: Integral b => b -> (k :~> f) g -> (k :~> f) g #

(~) (k -> *) f g => Monoid ((:~>) k f g) Source # 

Methods

mempty :: (k :~> f) g #

mappend :: (k :~> f) g -> (k :~> f) g -> (k :~> f) g #

mconcat :: [(k :~> f) g] -> (k :~> f) g #

Type Synonym for a Natural Transformation

type (~>) f g = forall x. f x -> g x infixr 0 Source #

A natural transformation from f to g.

Conversion functions between the newtype and the synonym

wrapNT :: (forall a. f a -> g a) -> f :~> g Source #

wrapNT builds our natural transformation abstraction out of a natural transformation function.

An alias to NT provided for symmetry with unwrapNT.

unwrapNT :: Transformation f g t => t -> forall a. f a -> g a Source #

unwrapNT is the nonfix version of #. It is used to break natural transformation wrappers, including :~>.

Class for Natural Transformations

class Transformation f g t | t -> f g where Source #

A (natural) transformation is inside t, and contains f and g (typically Functors).

The order of arguments allows the use of GeneralizedNewtypeDeriving to wrap a :~>, but maintain the Transformation constraint. Thus, # can be used on abstract data types.

Minimal complete definition

(#)

Methods

(#) :: t -> forall a. f a -> g a infix 0 Source #

The invocation method for a natural transformation.

Instances

Transformation k f g ((:~>) k f g) Source # 

Methods

(#) :: t -> forall a. g a -> (k :~> f) g a Source #

Transformation * f IO (Object f) Source # 

Methods

(#) :: t -> forall a. IO a -> Object f a Source #