{-# LANGUAGE MultiParamTypeClasses #-}

{-| Module  : FiniteCategories
Description : The __1__ category contains one object and its identity.
Copyright   : Guillaume Sabbagh 2022
License     : GPL-3
Maintainer  : guillaumesabbagh@protonmail.com
Stability   : experimental
Portability : portable

The __1__ category contains one object and its identity.

You can construct it using 'NumberCategory', it is defined as a standalone category because it is often used unlike other number categories.
-}

module Math.FiniteCategories.One
(
    One(..)
)
where
    import          Math.FiniteCategory
    import          Math.IO.PrettyPrint
    
    import          Data.WeakSet.Safe
    
    -- | 'One' is a datatype used as the object type, the morphism type and the category type of __1__.

    data One = One deriving (One -> One -> Bool
(One -> One -> Bool) -> (One -> One -> Bool) -> Eq One
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: One -> One -> Bool
$c/= :: One -> One -> Bool
== :: One -> One -> Bool
$c== :: One -> One -> Bool
Eq, Int -> One -> ShowS
[One] -> ShowS
One -> String
(Int -> One -> ShowS)
-> (One -> String) -> ([One] -> ShowS) -> Show One
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [One] -> ShowS
$cshowList :: [One] -> ShowS
show :: One -> String
$cshow :: One -> String
showsPrec :: Int -> One -> ShowS
$cshowsPrec :: Int -> One -> ShowS
Show)
    
    instance Morphism One One where
        source :: One -> One
source One
One = One
One
        target :: One -> One
target One
One = One
One
        @? :: One -> One -> Maybe One
(@?) One
One One
One = One -> Maybe One
forall a. a -> Maybe a
Just One
One
    
    instance Category One One One where
        identity :: Morphism One One => One -> One -> One
identity One
One One
One = One
One
        ar :: Morphism One One => One -> One -> One -> Set One
ar One
One One
One One
One = [One] -> Set One
forall a. [a] -> Set a
set [One
One]
    
    instance FiniteCategory One One One where
        ob :: One -> Set One
ob One
One = [One] -> Set One
forall a. [a] -> Set a
set [One
One]
    
    instance PrettyPrint One where
        pprint :: One -> String
pprint = One -> String
forall a. Show a => a -> String
show