cifl-math-library-1.1.1.0: Math libraries
Safe HaskellSafe
LanguageHaskell2010

Math.Tools.NaturalTransformation

Synopsis

Documentation

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

Constructors

NatTrans 

Fields

Instances

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

Defined in Math.Tools.NaturalTransformation

Methods

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

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

type MaybeNT m = Maybe :~> m Source #

type EitherNT a m = Either a :~> m Source #

type PairNT a m = (,) a :~> m Source #

type IndexNT a m = (->) a :~> m Source #

type ListNT m = List :~> m Source #

type IMT m = I :~> m Source #

type IOMT m = m :~> IO Source #

type NondetMT m = m :~> List Source #

type FailMT m = m :~> Maybe Source #

type AltMT a m = m :~> Either a Source #

type FunctorMT a m = m :~> (->) a Source #

type MonadNT m = (m :*: m) :~> m Source #

type ComonadNT m = m :~> (m :*: m) Source #

type TransposeNT m n = (m :*: n) :~> (n :*: m) Source #

type (::*::) row col elem = ((:==:) row :*: (:==:) col) elem Source #

duplicateMT :: Comonad m => m :~> (m :*: m) Source #

joinMT :: Monad m => (m :*: m) :~> m Source #

vert :: (g :~> h) -> (f :~> g) -> f :~> h Source #

horiz :: Functor h => (h :~> k) -> (f :~> g) -> (h :*: f) :~> (k :*: g) Source #

map_natural_matrix :: (Functor f, Functor h) => (f :~> g) -> (h :~> i) -> (a -> b) -> (f :*: h) a -> (g :*: i) b Source #

data Day f g c Source #

Constructors

forall a b. Day ((a, b) -> c) (f a) (g b) 

convolve :: (Functor f, Functor g) => Day f g c -> (f :*: g) c Source #

convolve_trans :: (Functor f, Functor g) => Day f g :~> (f :*: g) Source #

map_rows :: Functor h => (f :~> g) -> (h :*: f) :~> (h :*: g) Source #

map_columns :: (f :~> g) -> (f :*: h) :~> (g :*: h) Source #

mapMatrix :: (Functor f, Functor g) => (f :~> f') -> (g :~> g') -> (a -> b) -> (f :*: g) a -> (f' :*: g') b Source #

rec_map :: Functor f => (f :~> g) -> Rec f -> Rec g Source #

transform_map :: (Functor f, Functor g) => Coalgebra f a -> (f :~> g) -> Algebra g b -> a -> b Source #

tmap :: (InitialAlgebra f a, FinalCoalgebra g b) => (f :~> g) -> a -> b Source #

tapp :: Functor f => (f :~> g) -> (a -> b) -> f a -> g b Source #

unyoneda :: Category cat => (cat a :~> f) -> f a Source #

yoneda_function :: Functor t => t a -> (->) a :~> t Source #

inverse_horiz :: CoFunctor k => (f :~> k) -> (f' :~> k') -> (f :*: k') :~> (k :*: f') Source #

first_trans :: (y -> x) -> (->) (x, d) :~> (->) (y, d) Source #

join_trans :: Monad m => (m :*: m) :~> m Source #

data f :<~>: g Source #

Constructors

NaturalIso 

Fields

Instances

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

Defined in Math.Tools.NaturalTransformation

Methods

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

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

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

vertIso :: (g :<~>: h) -> (f :<~>: g) -> f :<~>: h Source #

horizIso :: (Functor f, Functor f') => (f :<~>: f') -> (g :<~>: g') -> (f :*: g) :<~>: (f' :*: g') Source #

isoMatrix :: (Functor g, Functor g') => (f :<~>: (g :*: h)) -> (g :<~>: g') -> (h :<~>: h') -> f :<~>: (g' :*: h') Source #

isoMatrix_ :: Functor g' => (f :<~>: ((->) row :*: (->) col)) -> ((->) row :<~>: g') -> ((->) col :<~>: h') -> f :<~>: (g' :*: h') Source #

outerIso :: Functor g' => ((->) row :<~>: g') -> ((->) col :<~>: h') -> ((->) row :*: (->) col) :<~>: (g' :*: h') Source #

matrixFrom :: Functor g => (row -> col -> a) -> ((->) row :<~>: g) -> ((->) col :<~>: h) -> (g :*: h) a Source #

matrixIso :: (Functor f, Functor f', Functor g, Functor g') => (f :<~>: f') -> (g :<~>: g') -> (a :==: b) -> (f :*: g) a :==: (f' :*: g') b Source #

runNaturalIso :: (f :<~>: g) -> f a :==: g a Source #

newtype (f :~~> g) a Source #

Constructors

NaturalTrans 

Fields

transform_matrix :: Applicative f' => ((f :~~> f') :*: g) a -> (f' :*: (g :~~> g')) a -> (f :*: g) a -> (f' :*: g') a Source #

newtype NaturalTransA (arr :: k -> k -> *) f g a Source #

Constructors

NaturalTransA 

Fields

newtype NatTransA (arr :: k -> k -> *) f g Source #

Constructors

NatTransA 

Fields

Instances

Instances details
Category arr => Category (NatTransA arr :: (k2 -> k1) -> (k2 -> k1) -> Type) Source # 
Instance details

Defined in Math.Tools.NaturalTransformation

Methods

id :: forall (a :: k). NatTransA arr a a #

(.) :: forall (b :: k) (c :: k) (a :: k). NatTransA arr b c -> NatTransA arr a b -> NatTransA arr a c #

id_transA :: Arrow arr => NatTransA arr f f Source #

horizA :: (Arrow arr, FunctorArrow k arr arr) => NatTransA arr h k -> NatTransA arr f g -> NatTransA arr (h :*: f) (k :*: g) Source #

vertA :: Arrow arr => NatTransA arr g h -> NatTransA arr f g -> NatTransA arr f h Source #

invertNatTransA :: NatTransA arr f g -> NatTransA (OpA arr) g f Source #

coyonedaA :: (Category cat, ArrowApply arr, ArrowChoice arr) => arr (NatTransA arr (OpA cat a) f) (f a) Source #

For exposition of coyonedaA, see Bartosz Milewski's youtube videos https://www.youtube.com/watch?v=p_ydgYm9-yg

unyonedaA :: (Category cat, ArrowApply arr) => arr (NatTransA arr (cat a) f) (f a) Source #

yonedaA :: (FunctorArrow f arr arr, ArrowApply arr) => f c -> NatTransA arr (arr c) f Source #

natTransToA :: (f :~> g) -> NatTransA (->) f g Source #

arrowNatTrans :: NatTransA (->) f g -> f :~> g Source #