{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} {-| Module : FiniteCategories Description : An 'OrdinalCategory' is a 'TotalOrder' category where the total order is an order induced by ordinal numbers. Copyright : Guillaume Sabbagh 2022 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable An 'OrdinalCategory' is a 'TotalOrder' category where the total order is an order induced by ordinal numbers. Concretely the type parameter must implement the Enum typeclass. For example, the 'TotalOrder' category induced by (R,<=) is not an 'OrdinalCategory' whereas (N,<=) is. It induces a non trivial generating set of arrows thanks to the 'succ' function. -} module Math.Categories.OrdinalCategory ( OrdinalCategory(..), module Math.Categories.TotalOrder ) where import Math.Category import Math.Categories.FunctorCategory import Math.Categories.ConeCategory import Math.Categories.TotalOrder import Math.IO.PrettyPrint import Data.WeakSet.Safe import qualified Data.WeakMap as Map import Data.WeakMap.Safe -- | An 'OrdinalCategory' is a 'TotalOrder' where the type /a/ follows the Enum typeclass. newtype OrdinalCategory a = OrdinalCategory (TotalOrder a) deriving (Eq, Show) instance (Enum a, Ord a) => Category (OrdinalCategory a) (IsSmallerThan a) a where ar _ x y | x <= y = set [IsSmallerThan x y] | otherwise = set [] identity _ x = IsSmallerThan x x -- | An 'OrdinalCategory' is generated by morphisms from a number to its successor. genAr _ x y | x == y = set [IsSmallerThan x x] | (succ x) == y = set [IsSmallerThan x y] | otherwise = set [] decompose _ (IsSmallerThan x y) | x == y = [IsSmallerThan x y] | otherwise = reverse $ (\n -> IsSmallerThan n (succ n)) <$> [x..(pred y)] instance (Show a) => PrettyPrint (OrdinalCategory a) where pprint = show