{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
module NumHask.Algebra.Group
( Magma (..),
Unital (..),
Associative,
Commutative,
Absorbing (..),
Invertible (..),
Idempotent,
Group,
AbelianGroup,
)
where
import Prelude
class Magma a where
infix 3 ⊕
(⊕) :: a -> a -> a
instance (Magma b) => Magma (a -> b) where
a -> b
f ⊕ :: (a -> b) -> (a -> b) -> a -> b
⊕ a -> b
g = \a
a -> a -> b
f a
a forall a. Magma a => a -> a -> a
⊕ a -> b
g a
a
class
(Magma a) =>
Unital a
where
unit :: a
instance (Unital b) => Unital (a -> b) where
{-# INLINE unit #-}
unit :: a -> b
unit a
_ = forall a. Unital a => a
unit
class
(Magma a) =>
Associative a
instance (Associative b) => Associative (a -> b)
class
(Magma a) =>
Commutative a
instance (Commutative b) => Commutative (a -> b)
class
(Magma a) =>
Invertible a
where
inv :: a -> a
instance (Invertible b) => Invertible (a -> b) where
{-# INLINE inv #-}
inv :: (a -> b) -> a -> b
inv a -> b
f = forall a. Invertible a => a -> a
inv forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f
class (Associative a, Unital a, Invertible a) => Group a
instance (Associative a, Unital a, Invertible a) => Group a
class
(Magma a) =>
Absorbing a
where
absorb :: a
instance (Absorbing b) => Absorbing (a -> b) where
{-# INLINE absorb #-}
absorb :: a -> b
absorb a
_ = forall a. Absorbing a => a
absorb
class
(Magma a) =>
Idempotent a
instance (Idempotent b) => Idempotent (a -> b)
class (Associative a, Unital a, Invertible a, Commutative a) => AbelianGroup a
instance (Associative a, Unital a, Invertible a, Commutative a) => AbelianGroup a