{-# LANGUAGE MultiParamTypeClasses #-} {-| Module : FiniteCategories Description : The __'V'__ category contains two arrows pointing to the same object. It is the opposite of __'Hat'__. Copyright : Guillaume Sabbagh 2022 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable The __'V'__ category contains two arrows pointing to the same object. The shape of the __'V'__ category is the following : @`B` -`F`-> `A` <-`G`- `C`@ -} module Math.FiniteCategories.V ( VOb(..), VAr(..), V(..) ) where import Math.FiniteCategory import Math.IO.PrettyPrint import Data.WeakSet.Safe -- | Objects of the __'V'__ category. data VOb = VA | VB | VC deriving (Eq, Show) -- | Morphisms of the __'V'__ category. data VAr = VIdA | VIdB | VIdC | VF | VG deriving (Eq, Show) -- | The __'V'__ category. data V = V deriving (Eq, Show) instance Morphism VAr VOb where source VIdA = VA source VIdB = VB source VIdC = VC source VF = VB source VG = VC target VIdA = VA target VIdB = VB target VIdC = VC target _ = VA (@?) VIdA VIdA = Just VIdA (@?) VIdB VIdB = Just VIdB (@?) VF VIdB = Just VF (@?) VG VIdC = Just VG (@?) VIdC VIdC = Just VIdC (@?) VIdA VF = Just VF (@?) VIdA VG = Just VG (@?) _ _ = Nothing instance Category V VAr VOb where identity _ VA = VIdA identity _ VB = VIdB identity _ VC = VIdC ar _ VA VA = set [VIdA] ar _ VB VA = set [VF] ar _ VB VB = set [VIdB] ar _ VC VA = set [VG] ar _ VC VC = set [VIdC] ar _ _ _ = set [] instance FiniteCategory V VAr VOb where ob _ = set [VA, VB, VC] instance PrettyPrint VOb where pprint VA = "A" pprint VB = "B" pprint VC = "C" instance PrettyPrint VAr where pprint VIdA = "IdA" pprint VIdB = "IdB" pprint VIdC = "IdC" pprint VF = "f" pprint VG = "g" instance PrettyPrint V where pprint = show