{-# LANGUAGE MultiParamTypeClasses #-} {-| Module : FiniteCategories Description : The __'Parallel'__ category contains two parallel arrows. Copyright : Guillaume Sabbagh 2022 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 Math.FiniteCategories.Parallel ( ParallelOb(..), ParallelAr(..), Parallel(..) ) where import Math.FiniteCategory import Math.IO.PrettyPrint import Data.WeakSet.Safe -- | Objects of the __'Parallel'__ category. data ParallelOb = ParallelA | ParallelB deriving (Eq, Show) -- | Morphisms of the __'Parallel'__ category. data ParallelAr = ParallelIdA | ParallelIdB | ParallelF | ParallelG deriving (Eq, Show) -- | The __'Parallel'__ category. data Parallel = Parallel deriving (Eq, Show) instance Morphism ParallelAr ParallelOb where source ParallelIdA = ParallelA source ParallelIdB = ParallelB source _ = ParallelA target ParallelIdA = ParallelA target ParallelIdB = ParallelB target _ = ParallelB (@?) ParallelIdA ParallelIdA = Just ParallelIdA (@?) ParallelF ParallelIdA = Just ParallelF (@?) ParallelG ParallelIdA = Just ParallelG (@?) ParallelIdB ParallelIdB = Just ParallelIdB (@?) ParallelIdB ParallelF = Just ParallelF (@?) ParallelIdB ParallelG = Just ParallelG (@?) _ _ = Nothing instance Category Parallel ParallelAr ParallelOb where identity _ ParallelA = ParallelIdA identity _ ParallelB = ParallelIdB ar _ ParallelA ParallelA = set [ParallelIdA] ar _ ParallelA ParallelB = set [ParallelF,ParallelG] ar _ ParallelB ParallelB = set [ParallelIdB] ar _ _ _ = set [] instance FiniteCategory Parallel ParallelAr ParallelOb where ob _ = set [ParallelA,ParallelB] instance PrettyPrint ParallelOb where pprint ParallelA = "A" pprint ParallelB = "B" instance PrettyPrint ParallelAr where pprint ParallelIdA = "IdA" pprint ParallelIdB = "IdB" pprint ParallelF = "f" pprint ParallelG = "g" instance PrettyPrint Parallel where pprint Parallel = "Parallel"