{-# LANGUAGE MultiParamTypeClasses #-}
module Math.FiniteCategories.DiscreteCategory
(
DiscreteMorphism(..),
DiscreteCategory(..),
discreteCategory
)
where
import Math.FiniteCategory
import Math.Categories.Galaxy
import Math.FiniteCategories.FullSubcategory
import Data.WeakSet (Set)
import Data.WeakSet.Safe
type DiscreteCategory a = FullSubcategory (Galaxy a) (StarIdentity a) a
type DiscreteMorphism a = StarIdentity a
discreteCategory :: Set a -> DiscreteCategory a
discreteCategory :: forall a. Set a -> DiscreteCategory a
discreteCategory Set a
s = Galaxy a -> Set a -> FullSubcategory (Galaxy a) (StarIdentity a) a
forall c m o. c -> Set o -> FullSubcategory c m o
FullSubcategory Galaxy a
forall a. Galaxy a
Galaxy Set a
s