data-category-0.3.1.1: Restricted categories

Portabilitynon-portable
Stabilityexperimental
Maintainersjoerd@w3future.com

Data.Category.Monoidal

Description

 

Documentation

class Functor f => HasUnit f whereSource

Associated Types

type Unit f :: *Source

Methods

unitObject :: f -> Obj (Cod f) (Unit f)Source

class HasUnit f => TensorProduct f whereSource

Methods

leftUnitor :: Cod f ~ ~> => f -> Obj (Cod f) a -> (f :% (Unit f, a)) ~> aSource

leftUnitorInv :: Cod f ~ ~> => f -> Obj (Cod f) a -> a ~> (f :% (Unit f, a))Source

rightUnitor :: Cod f ~ ~> => f -> Obj (Cod f) a -> (f :% (a, Unit f)) ~> aSource

rightUnitorInv :: Cod f ~ ~> => f -> Obj (Cod f) a -> a ~> (f :% (a, Unit f))Source

associator :: Cod f ~ ~> => f -> Obj (Cod f) a -> Obj (Cod f) b -> Obj (Cod f) c -> (f :% (f :% (a, b), c)) ~> (f :% (a, f :% (b, c)))Source

associatorInv :: Cod f ~ ~> => f -> Obj (Cod f) a -> Obj (Cod f) b -> Obj (Cod f) c -> (f :% (a, f :% (b, c))) ~> (f :% (f :% (a, b), c))Source

data MonoidObject f a Source

Constructors

MonoidObject 

Fields

unit :: Cod f ~ ~> => Unit f ~> a
 
multiply :: Cod f ~ ~> => (f :% (a, a)) ~> a
 

data ComonoidObject f a Source

Constructors

ComonoidObject 

Fields

counit :: Cod f ~ ~> => a ~> Unit f
 
comultiply :: Cod f ~ ~> => a ~> (f :% (a, a))
 

data MonoidAsCategory f m a b whereSource

Constructors

MonoidValue :: (TensorProduct f, Dom f ~ ~> :**: ~>, Cod f ~ ~>) => f -> MonoidObject f m -> (Unit f ~> m) -> MonoidAsCategory f m m m 

Instances

mkMonad :: (Functor f, Dom f ~ ~>, Cod f ~ ~>, Category ~>) => f -> (forall a. Obj ~> a -> Component (Id ~>) f a) -> (forall a. Obj ~> a -> Component (f :.: f) f a) -> Monad fSource

monadFunctor :: forall f. Monad f -> fSource

mkComonad :: (Functor f, Dom f ~ ~>, Cod f ~ ~>, Category ~>) => f -> (forall a. Obj ~> a -> Component f (Id ~>) a) -> (forall a. Obj ~> a -> Component f (f :.: f) a) -> Comonad fSource