natural-transformation-0.4.1: 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

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

Instances details
Transformation (f :: k -> Type) (g :: k -> Type) (f :~> g) Source # 
Instance details

Defined in Control.Natural

Methods

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

Category ((:~>) :: (k -> Type) -> (k -> Type) -> Type) Source # 
Instance details

Defined in Control.Natural

Methods

id :: forall (a :: k0). a :~> a #

(.) :: forall (b :: k0) (c :: k0) (a :: k0). (b :~> c) -> (a :~> b) -> a :~> c #

f ~ g => Monoid (f :~> g) Source # 
Instance details

Defined in Control.Natural

Methods

mempty :: f :~> g #

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

mconcat :: [f :~> g] -> f :~> g #

f ~ g => Semigroup (f :~> g) Source # 
Instance details

Defined in Control.Natural

Methods

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

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

stimes :: Integral b => b -> (f :~> g) -> 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.

Methods

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

The invocation method for a natural transformation.

Instances

Instances details
Transformation (f :: Type -> Type) IO (Object f) Source # 
Instance details

Defined in Control.Object

Methods

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

Transformation (f :: k -> Type) (g :: k -> Type) (f :~> g) Source # 
Instance details

Defined in Control.Natural

Methods

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