{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} {-| Module : FiniteCategories Description : The __'FinSet'__ category has finite sets as objects and functions as morphisms. Copyright : Guillaume Sabbagh 2022 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable The __'FinSet'__ category has finite sets as objects and functions as morphisms. Finite sets are represented by weak sets from Data.WeakSet and functions by enriched weak maps from Data.WeakMap. These structures are homogeneous, meaning you can only have sets containing one type of objects in a given 'FinSet' category. See the category __'PureSet'__ for the category of sets which can be arbitrarily nested. -} module Math.Categories.FinSet ( -- * Function Function(..), (||!||), -- * __FinSet__ FinSet(..), ) where import Math.Category import Math.Categories.ConeCategory import Math.Categories.FunctorCategory import Math.FiniteCategories.DiscreteCategory import Math.IO.PrettyPrint import Data.WeakSet (Set) import qualified Data.WeakSet as Set import Data.WeakSet.Safe import Data.WeakMap (Map) import qualified Data.WeakMap as Map import Data.WeakMap.Safe import Data.List (nub) import Data.Maybe (fromJust) -- | A 'Function' (finite function) is a weak map enriched with a codomain. -- -- We have to store the codomain to retrieve the target set of a morphism in __'FinSet'__. data Function a = Function { function :: Map a a, codomain :: Set a } deriving (Eq, Show) instance (Eq a) => Morphism (Function a) (Set a) where source = domain.function target = codomain (@?) f2 f1 | target f1 == source f2 = Just Function{function = (function f2) |.| (function f1), codomain = codomain f2} | otherwise = Nothing -- | A function to apply a 'Function' to an object in the domain of the 'Function'. (||!||) :: (Eq a) => Function a -> a -> a (||!||) f x = (function f) |!| x -- | __'FinSet'__ is the category of finite sets. data FinSet a = FinSet deriving (Eq, Show) instance (Eq a) => Category (FinSet a) (Function a) (Set a) where identity _ s = Function {function = idFromSet s, codomain = s} ar _ s t | Set.null s = set [Function{function = weakMap [], codomain = t}] | Set.null t = set [] | otherwise = (\x -> Function{function = x, codomain = t}) <$> functions where domain = setToList s images = (t |^| (length domain)) functions = weakMap <$> zip domain <$> images -- instance (Eq a) => HasFiniteProducts (FinSet a) (Set a) (Function [a]) (Set [a]) where -- product _ diag2 = result -- where -- prod = cartesianProductOfSets (elems (omap diag2)) -- diag1 = constantDiagram (source diag2) FinSet prod -- mapping i = memorizeFunction (\_ -> (!! i) <$> prod) prod -- Just result = naturalTransformationToCone $ unsafeNaturalTransformation diag1 diag2 (weakMap [(i,Function {function=mapping i, codomain = image (mapping i)}) | i <- [0..((Map.size (omap diag2))-1)]]) instance (PrettyPrint a, Eq a) => PrettyPrint (Function a) where pprint = pprint.function instance (PrettyPrint a, Eq a) => PrettyPrint (FinSet a) where pprint = show