{-# LANGUAGE NoImplicitPrelude #-}
module MathObj.Monoid where
import qualified Algebra.PrincipalIdealDomain as PID
import Algebra.PrincipalIdealDomain (gcd, lcm, )
import Algebra.Additive (zero, )
import Algebra.Monoid (C, idt, (<*>), )
import NumericPrelude.Base
newtype GCD a = GCD {runGCD :: a}
deriving (Show, Eq)
instance PID.C a => C (GCD a) where
idt = GCD zero
(GCD x) <*> (GCD y) = GCD (gcd x y)
newtype LCM a = LCM {runLCM :: a}
deriving (Show, Eq)
instance PID.C a => C (LCM a) where
idt = LCM zero
(LCM x) <*> (LCM y) = LCM (lcm x y)
newtype Min a = Min {runMin :: Maybe a}
deriving (Show, Eq)
instance Ord a => C (Min a) where
idt = Min Nothing
(Min x) <*> (Min y) = Min $
maybe y (\x' -> maybe x (Just . min x') y) x
newtype Max a = Max {runMax :: Maybe a}
deriving (Show, Eq)
instance Ord a => C (Max a) where
idt = Max Nothing
(Max x) <*> (Max y) = Max $
maybe y (\x' -> maybe x (Just . max x') y) x