{-# LANGUAGE MultiParamTypeClasses #-} {-| Module : FiniteCategories Description : The parallel category contains two parallel arrows. Copyright : Guillaume Sabbagh 2021 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable The parallel category contains two objects `A` and `B` and two morphisms @`F` : `A` -> `B`@ and @`G` : `A` -> `B`@. -} module UsualCategories.Parallel ( ParallelOb(..), ParallelAr(..), Parallel(..) ) where import FiniteCategory.FiniteCategory import IO.PrettyPrint -- | Object of the parallel category. data ParallelOb = A | B deriving (Eq, Show) -- | Morphism of the parallel category. data ParallelAr = IdA | IdB | F | G deriving (Eq, Show) -- | The parallel category. data Parallel = Parallel deriving (Eq, Show) instance Morphism ParallelAr ParallelOb where source IdA = A source IdB = B source _ = A target IdA = A target IdB = B target _ = B (@) IdA IdA = IdA (@) F IdA = F (@) G IdA = G (@) IdB IdB = IdB (@) IdB F = F (@) IdB G = G instance FiniteCategory Parallel ParallelAr ParallelOb where ob = const [A,B] identity _ A = IdA identity _ B = IdB ar _ A A = [IdA] ar _ A B = [F,G] ar _ B B = [IdB] ar _ _ _ = [] instance GeneratedFiniteCategory Parallel ParallelAr ParallelOb where genAr = defaultGenAr decompose = defaultDecompose instance PrettyPrintable ParallelOb where pprint = show instance PrettyPrintable ParallelAr where pprint = show instance PrettyPrintable Parallel where pprint = show