{-# LANGUAGE MultiParamTypeClasses #-} {-| Module : FiniteCategories Description : The __2__ category contains two object `A` and `B` and a morphism @`F` : `A` -> `B`@. Copyright : Guillaume Sabbagh 2021 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable The __2__ category contains two object `A` and `B` and a morphism @f : `A` -> `B`@ (and of course two identities). -} module UsualCategories.Two ( TwoOb(..), TwoAr(..), Two(..) ) where import FiniteCategory.FiniteCategory import IO.PrettyPrint -- | Object of the __2__ category. data TwoOb = A | B deriving (Eq, Show) -- | Morphism of the __2__ category. data TwoAr = IdA | IdB | F deriving (Eq,Show) -- | The __2__ category. data Two = Two deriving (Eq,Show) instance Morphism TwoAr TwoOb where source IdA = A source IdB = B source F = A target IdA = A target IdB = B target F = B (@) IdA IdA = IdA (@) IdB IdB = IdB (@) F IdA = F (@) IdB F = F (@) x y = error ("Invalid composition of TwoMorph : "++show x++" * "++show y) instance FiniteCategory Two TwoAr TwoOb where ob = const [A,B] identity _ A = IdA identity _ B = IdB ar _ A A = [IdA] ar _ A B = [F] ar _ B B = [IdB] ar _ _ _ = [] instance GeneratedFiniteCategory Two TwoAr TwoOb where genAr = defaultGenAr decompose = defaultDecompose instance PrettyPrintable TwoOb where pprint = show instance PrettyPrintable TwoAr where pprint = show instance PrettyPrintable Two where pprint = show