categories-1.0.7: Categories

Copyright2008-2010 Edward Kmett
LicenseBSD
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable (class-associated types)
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Category.Cartesian

Contents

Description

 

Synopsis

(Co)Cartesian categories

class (Symmetric k (Product k), Monoidal k (Product k)) => Cartesian k where Source

Minimum definition:

fst, snd, diag
fst, snd, (&&&)

Minimal complete definition

fst, snd

Associated Types

type Product k :: * -> * -> * Source

Methods

fst :: Product k a b `k` a Source

snd :: Product k a b `k` b Source

diag :: a `k` Product k a a Source

(&&&) :: (a `k` b) -> (a `k` c) -> a `k` Product k b c infixr 3 Source

Instances

Cartesian (->) 

bimapProduct :: Cartesian k => k a c -> k b d -> Product k a b `k` Product k c d Source

free construction of Bifunctor for the product Bifunctor Product k if (&&&) is known

braidProduct :: Cartesian k => k (Product k a b) (Product k b a) Source

free construction of Braided for the product Bifunctor Product k

associateProduct :: Cartesian k => Product k (Product k a b) c `k` Product k a (Product k b c) Source

free construction of Associative for the product Bifunctor Product k

disassociateProduct :: Cartesian k => Product k a (Product k b c) `k` Product k (Product k a b) c Source

free construction of Disassociative for the product Bifunctor Product k

class (Monoidal k (Sum k), Symmetric k (Sum k)) => CoCartesian k where Source

Minimal complete definition

inl, inr

Associated Types

type Sum k :: * -> * -> * Source

Methods

inl :: a `k` Sum k a b Source

inr :: b `k` Sum k a b Source

codiag :: Sum k a a `k` a Source

(|||) :: k a c -> k b c -> Sum k a b `k` c infixr 2 Source

Instances

bimapSum :: CoCartesian k => k a c -> k b d -> Sum k a b `k` Sum k c d Source

free construction of Bifunctor for the coproduct Bifunctor Sum k if (|||) is known

braidSum :: CoCartesian k => Sum k a b `k` Sum k b a Source

free construction of Braided for the coproduct Bifunctor Sum k

associateSum :: CoCartesian k => Sum k (Sum k a b) c `k` Sum k a (Sum k b c) Source

free construction of Associative for the coproduct Bifunctor Sum k

disassociateSum :: CoCartesian k => Sum k a (Sum k b c) `k` Sum k (Sum k a b) c Source

free construction of Disassociative for the coproduct Bifunctor Sum k