{-# language BangPatterns #-}
{-# language CPP #-}
{-# language DerivingStrategies #-}
{-# language FlexibleInstances #-}
{-# language PatternSynonyms #-}
{-# language Safe #-}
#if MIN_VERSION_base(4,12,0)
{-# language TypeOperators #-}
#endif
{-# language ViewPatterns #-}
module Data.Group
(
Group(..)
, (><)
, conjugate
, unconjugate
, pattern Conjugate
, Order(..)
, pattern Infinitary
, pattern Finitary
, order
, Abelianizer(..)
, abelianize
, commutate
, pattern Abelianized
, pattern Quotiented
, AbelianGroup
) where
import Data.Bool
import Data.Functor.Const
#if __GLASGOW_HASKELL__ > 804
import Data.Functor.Contravariant
#endif
import Data.Functor.Identity
import Data.Semigroup (stimes)
import Data.Int
import Data.Monoid
import Data.Ord
import Data.Proxy
import Data.Ratio
import Data.Word
import Numeric.Natural
#if MIN_VERSION_base(4,12,0)
import GHC.Generics
#endif
import Prelude hiding (negate, exponent)
import qualified Prelude
infixr 6 ><
class Monoid a => Group a where
invert :: a -> a
invert a
a = a
forall a. Monoid a => a
mempty a -> a -> a
forall a. Group a => a -> a -> a
`minus` a
a
{-# inline invert #-}
gtimes :: (Integral n) => n -> a -> a
gtimes n
n a
a
| n
n n -> n -> Bool
forall a. Eq a => a -> a -> Bool
== n
0 = a
forall a. Monoid a => a
mempty
| n
n n -> n -> Bool
forall a. Ord a => a -> a -> Bool
> n
0 = n -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes n
n a
a
| Bool
otherwise = n -> a -> a
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes (n -> n
forall a. Num a => a -> a
abs n
n) (a -> a
forall a. Group a => a -> a
invert a
a)
{-# inline gtimes #-}
minus :: a -> a -> a
minus a
a a
b = a
a a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a -> a
forall a. Group a => a -> a
invert a
b
{-# inline minus #-}
{-# minimal invert | minus #-}
instance Group () where
invert :: () -> ()
invert = () -> ()
forall a. a -> a
id
{-# inline invert #-}
instance Group b => Group (a -> b) where
invert :: (a -> b) -> a -> b
invert a -> b
f = b -> b
forall a. Group a => a -> a
invert (b -> b) -> (a -> b) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f
{-# inline invert #-}
instance Group a => Group (Dual a) where
invert :: Dual a -> Dual a
invert (Dual a
a) = a -> Dual a
forall a. a -> Dual a
Dual (a -> a
forall a. Group a => a -> a
invert a
a)
{-# inline invert #-}
instance Group a => Group (Down a) where
invert :: Down a -> Down a
invert (Down a
a) = a -> Down a
forall a. a -> Down a
Down (a -> a
forall a. Group a => a -> a
invert a
a)
{-# inline invert #-}
instance Group a => Group (Endo a) where
invert :: Endo a -> Endo a
invert (Endo a -> a
a) = (a -> a) -> Endo a
forall a. (a -> a) -> Endo a
Endo (a -> a
forall a. Group a => a -> a
invert (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
a)
{-# inline invert #-}
#if __GLASGOW_HASKELL__ > 804
instance Group (Equivalence a) where
invert :: Equivalence a -> Equivalence a
invert (Equivalence a -> a -> Bool
p) = (a -> a -> Bool) -> Equivalence a
forall a. (a -> a -> Bool) -> Equivalence a
Equivalence ((a -> a -> Bool) -> Equivalence a)
-> (a -> a -> Bool) -> Equivalence a
forall a b. (a -> b) -> a -> b
$ \a
a a
b -> Bool -> Bool
not (a -> a -> Bool
p a
a a
b)
{-# inline invert #-}
instance Group (Comparison a) where
invert :: Comparison a -> Comparison a
invert (Comparison a -> a -> Ordering
p) = (a -> a -> Ordering) -> Comparison a
forall a. (a -> a -> Ordering) -> Comparison a
Comparison ((a -> a -> Ordering) -> Comparison a)
-> (a -> a -> Ordering) -> Comparison a
forall a b. (a -> b) -> a -> b
$ \a
a a
b -> Ordering -> Ordering
forall a. Group a => a -> a
invert (a -> a -> Ordering
p a
a a
b)
{-# inline invert #-}
instance Group (Predicate a) where
invert :: Predicate a -> Predicate a
invert (Predicate a -> Bool
p) = (a -> Bool) -> Predicate a
forall a. (a -> Bool) -> Predicate a
Predicate ((a -> Bool) -> Predicate a) -> (a -> Bool) -> Predicate a
forall a b. (a -> b) -> a -> b
$ \a
a -> Bool -> Bool
not (a -> Bool
p a
a)
{-# inline invert #-}
instance Group a => Group (Op a b) where
invert :: Op a b -> Op a b
invert (Op b -> a
f) = (b -> a) -> Op a b
forall a b. (b -> a) -> Op a b
Op ((b -> a) -> Op a b) -> (b -> a) -> Op a b
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Group a => a -> a
invert (a -> a) -> (b -> a) -> b -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> a
f
{-# inline invert #-}
#endif
instance Group Any where
invert :: Any -> Any
invert (Any Bool
b) = Bool -> Any
Any (Bool -> Any) -> Bool -> Any
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Bool -> Bool
forall a. a -> a -> Bool -> a
bool Bool
True Bool
False Bool
b
{-# inline invert #-}
instance Group All where
invert :: All -> All
invert (All Bool
b) = Bool -> All
All (Bool -> All) -> Bool -> All
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Bool -> Bool
forall a. a -> a -> Bool -> a
bool Bool
True Bool
False Bool
b
{-# inline invert #-}
instance Group (Sum Integer) where
invert :: Sum Integer -> Sum Integer
invert = Sum Integer -> Sum Integer
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Rational) where
invert :: Sum Rational -> Sum Rational
invert = Sum Rational -> Sum Rational
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Int) where
invert :: Sum Int -> Sum Int
invert = Sum Int -> Sum Int
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Int8) where
invert :: Sum Int8 -> Sum Int8
invert = Sum Int8 -> Sum Int8
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Int16) where
invert :: Sum Int16 -> Sum Int16
invert = Sum Int16 -> Sum Int16
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Int32) where
invert :: Sum Int32 -> Sum Int32
invert = Sum Int32 -> Sum Int32
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Int64) where
invert :: Sum Int64 -> Sum Int64
invert = Sum Int64 -> Sum Int64
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Word) where
invert :: Sum Word -> Sum Word
invert = Sum Word -> Sum Word
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Word8) where
invert :: Sum Word8 -> Sum Word8
invert = Sum Word8 -> Sum Word8
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Word16) where
invert :: Sum Word16 -> Sum Word16
invert = Sum Word16 -> Sum Word16
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Word32) where
invert :: Sum Word32 -> Sum Word32
invert = Sum Word32 -> Sum Word32
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum Word64) where
invert :: Sum Word64 -> Sum Word64
invert = Sum Word64 -> Sum Word64
forall a. Num a => a -> a
Prelude.negate
{-# inline invert #-}
instance Group (Sum (Ratio Int)) where
invert :: Sum (Ratio Int) -> Sum (Ratio Int)
invert = Ratio Int -> Sum (Ratio Int)
forall a. a -> Sum a
Sum (Ratio Int -> Sum (Ratio Int))
-> (Sum (Ratio Int) -> Ratio Int)
-> Sum (Ratio Int)
-> Sum (Ratio Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int -> Ratio Int
forall a. Num a => a -> a
Prelude.negate (Ratio Int -> Ratio Int)
-> (Sum (Ratio Int) -> Ratio Int) -> Sum (Ratio Int) -> Ratio Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Int) -> Ratio Int
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Int8)) where
invert :: Sum (Ratio Int8) -> Sum (Ratio Int8)
invert = Ratio Int8 -> Sum (Ratio Int8)
forall a. a -> Sum a
Sum (Ratio Int8 -> Sum (Ratio Int8))
-> (Sum (Ratio Int8) -> Ratio Int8)
-> Sum (Ratio Int8)
-> Sum (Ratio Int8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int8 -> Ratio Int8
forall a. Num a => a -> a
Prelude.negate (Ratio Int8 -> Ratio Int8)
-> (Sum (Ratio Int8) -> Ratio Int8)
-> Sum (Ratio Int8)
-> Ratio Int8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Int8) -> Ratio Int8
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Int16)) where
invert :: Sum (Ratio Int16) -> Sum (Ratio Int16)
invert = Ratio Int16 -> Sum (Ratio Int16)
forall a. a -> Sum a
Sum (Ratio Int16 -> Sum (Ratio Int16))
-> (Sum (Ratio Int16) -> Ratio Int16)
-> Sum (Ratio Int16)
-> Sum (Ratio Int16)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int16 -> Ratio Int16
forall a. Num a => a -> a
Prelude.negate (Ratio Int16 -> Ratio Int16)
-> (Sum (Ratio Int16) -> Ratio Int16)
-> Sum (Ratio Int16)
-> Ratio Int16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Int16) -> Ratio Int16
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Int32)) where
invert :: Sum (Ratio Int32) -> Sum (Ratio Int32)
invert = Ratio Int32 -> Sum (Ratio Int32)
forall a. a -> Sum a
Sum (Ratio Int32 -> Sum (Ratio Int32))
-> (Sum (Ratio Int32) -> Ratio Int32)
-> Sum (Ratio Int32)
-> Sum (Ratio Int32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int32 -> Ratio Int32
forall a. Num a => a -> a
Prelude.negate (Ratio Int32 -> Ratio Int32)
-> (Sum (Ratio Int32) -> Ratio Int32)
-> Sum (Ratio Int32)
-> Ratio Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Int32) -> Ratio Int32
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Int64)) where
invert :: Sum (Ratio Int64) -> Sum (Ratio Int64)
invert = Ratio Int64 -> Sum (Ratio Int64)
forall a. a -> Sum a
Sum (Ratio Int64 -> Sum (Ratio Int64))
-> (Sum (Ratio Int64) -> Ratio Int64)
-> Sum (Ratio Int64)
-> Sum (Ratio Int64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int64 -> Ratio Int64
forall a. Num a => a -> a
Prelude.negate (Ratio Int64 -> Ratio Int64)
-> (Sum (Ratio Int64) -> Ratio Int64)
-> Sum (Ratio Int64)
-> Ratio Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Int64) -> Ratio Int64
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Word)) where
invert :: Sum (Ratio Word) -> Sum (Ratio Word)
invert = Ratio Word -> Sum (Ratio Word)
forall a. a -> Sum a
Sum (Ratio Word -> Sum (Ratio Word))
-> (Sum (Ratio Word) -> Ratio Word)
-> Sum (Ratio Word)
-> Sum (Ratio Word)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word -> Ratio Word
forall a. Num a => a -> a
Prelude.negate (Ratio Word -> Ratio Word)
-> (Sum (Ratio Word) -> Ratio Word)
-> Sum (Ratio Word)
-> Ratio Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Word) -> Ratio Word
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Word8)) where
invert :: Sum (Ratio Word8) -> Sum (Ratio Word8)
invert = Ratio Word8 -> Sum (Ratio Word8)
forall a. a -> Sum a
Sum (Ratio Word8 -> Sum (Ratio Word8))
-> (Sum (Ratio Word8) -> Ratio Word8)
-> Sum (Ratio Word8)
-> Sum (Ratio Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word8 -> Ratio Word8
forall a. Num a => a -> a
Prelude.negate (Ratio Word8 -> Ratio Word8)
-> (Sum (Ratio Word8) -> Ratio Word8)
-> Sum (Ratio Word8)
-> Ratio Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Word8) -> Ratio Word8
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Word16)) where
invert :: Sum (Ratio Word16) -> Sum (Ratio Word16)
invert = Ratio Word16 -> Sum (Ratio Word16)
forall a. a -> Sum a
Sum (Ratio Word16 -> Sum (Ratio Word16))
-> (Sum (Ratio Word16) -> Ratio Word16)
-> Sum (Ratio Word16)
-> Sum (Ratio Word16)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word16 -> Ratio Word16
forall a. Num a => a -> a
Prelude.negate (Ratio Word16 -> Ratio Word16)
-> (Sum (Ratio Word16) -> Ratio Word16)
-> Sum (Ratio Word16)
-> Ratio Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Word16) -> Ratio Word16
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Word32)) where
invert :: Sum (Ratio Word32) -> Sum (Ratio Word32)
invert = Ratio Word32 -> Sum (Ratio Word32)
forall a. a -> Sum a
Sum (Ratio Word32 -> Sum (Ratio Word32))
-> (Sum (Ratio Word32) -> Ratio Word32)
-> Sum (Ratio Word32)
-> Sum (Ratio Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word32 -> Ratio Word32
forall a. Num a => a -> a
Prelude.negate (Ratio Word32 -> Ratio Word32)
-> (Sum (Ratio Word32) -> Ratio Word32)
-> Sum (Ratio Word32)
-> Ratio Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Word32) -> Ratio Word32
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Sum (Ratio Word64)) where
invert :: Sum (Ratio Word64) -> Sum (Ratio Word64)
invert = Ratio Word64 -> Sum (Ratio Word64)
forall a. a -> Sum a
Sum (Ratio Word64 -> Sum (Ratio Word64))
-> (Sum (Ratio Word64) -> Ratio Word64)
-> Sum (Ratio Word64)
-> Sum (Ratio Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word64 -> Ratio Word64
forall a. Num a => a -> a
Prelude.negate (Ratio Word64 -> Ratio Word64)
-> (Sum (Ratio Word64) -> Ratio Word64)
-> Sum (Ratio Word64)
-> Ratio Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum (Ratio Word64) -> Ratio Word64
forall a. Sum a -> a
getSum
{-# inline invert #-}
instance Group (Product Rational) where
invert :: Product Rational -> Product Rational
invert = Rational -> Product Rational
forall a. a -> Product a
Product (Rational -> Product Rational)
-> (Product Rational -> Rational)
-> Product Rational
-> Product Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Rational
forall a. Fractional a => a -> a
Prelude.recip (Rational -> Rational)
-> (Product Rational -> Rational) -> Product Rational -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product Rational -> Rational
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Natural)) where
invert :: Product (Ratio Natural) -> Product (Ratio Natural)
invert = Ratio Natural -> Product (Ratio Natural)
forall a. a -> Product a
Product (Ratio Natural -> Product (Ratio Natural))
-> (Product (Ratio Natural) -> Ratio Natural)
-> Product (Ratio Natural)
-> Product (Ratio Natural)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Natural -> Ratio Natural
forall a. Fractional a => a -> a
Prelude.recip (Ratio Natural -> Ratio Natural)
-> (Product (Ratio Natural) -> Ratio Natural)
-> Product (Ratio Natural)
-> Ratio Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Natural) -> Ratio Natural
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Int)) where
invert :: Product (Ratio Int) -> Product (Ratio Int)
invert = Ratio Int -> Product (Ratio Int)
forall a. a -> Product a
Product (Ratio Int -> Product (Ratio Int))
-> (Product (Ratio Int) -> Ratio Int)
-> Product (Ratio Int)
-> Product (Ratio Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int -> Ratio Int
forall a. Fractional a => a -> a
Prelude.recip (Ratio Int -> Ratio Int)
-> (Product (Ratio Int) -> Ratio Int)
-> Product (Ratio Int)
-> Ratio Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Int) -> Ratio Int
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Int8)) where
invert :: Product (Ratio Int8) -> Product (Ratio Int8)
invert = Ratio Int8 -> Product (Ratio Int8)
forall a. a -> Product a
Product (Ratio Int8 -> Product (Ratio Int8))
-> (Product (Ratio Int8) -> Ratio Int8)
-> Product (Ratio Int8)
-> Product (Ratio Int8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int8 -> Ratio Int8
forall a. Fractional a => a -> a
Prelude.recip (Ratio Int8 -> Ratio Int8)
-> (Product (Ratio Int8) -> Ratio Int8)
-> Product (Ratio Int8)
-> Ratio Int8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Int8) -> Ratio Int8
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Int16)) where
invert :: Product (Ratio Int16) -> Product (Ratio Int16)
invert = Ratio Int16 -> Product (Ratio Int16)
forall a. a -> Product a
Product (Ratio Int16 -> Product (Ratio Int16))
-> (Product (Ratio Int16) -> Ratio Int16)
-> Product (Ratio Int16)
-> Product (Ratio Int16)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int16 -> Ratio Int16
forall a. Fractional a => a -> a
Prelude.recip (Ratio Int16 -> Ratio Int16)
-> (Product (Ratio Int16) -> Ratio Int16)
-> Product (Ratio Int16)
-> Ratio Int16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Int16) -> Ratio Int16
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Int32)) where
invert :: Product (Ratio Int32) -> Product (Ratio Int32)
invert = Ratio Int32 -> Product (Ratio Int32)
forall a. a -> Product a
Product (Ratio Int32 -> Product (Ratio Int32))
-> (Product (Ratio Int32) -> Ratio Int32)
-> Product (Ratio Int32)
-> Product (Ratio Int32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int32 -> Ratio Int32
forall a. Fractional a => a -> a
Prelude.recip (Ratio Int32 -> Ratio Int32)
-> (Product (Ratio Int32) -> Ratio Int32)
-> Product (Ratio Int32)
-> Ratio Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Int32) -> Ratio Int32
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Int64)) where
invert :: Product (Ratio Int64) -> Product (Ratio Int64)
invert = Ratio Int64 -> Product (Ratio Int64)
forall a. a -> Product a
Product (Ratio Int64 -> Product (Ratio Int64))
-> (Product (Ratio Int64) -> Ratio Int64)
-> Product (Ratio Int64)
-> Product (Ratio Int64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Int64 -> Ratio Int64
forall a. Fractional a => a -> a
Prelude.recip (Ratio Int64 -> Ratio Int64)
-> (Product (Ratio Int64) -> Ratio Int64)
-> Product (Ratio Int64)
-> Ratio Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Int64) -> Ratio Int64
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Word)) where
invert :: Product (Ratio Word) -> Product (Ratio Word)
invert = Ratio Word -> Product (Ratio Word)
forall a. a -> Product a
Product (Ratio Word -> Product (Ratio Word))
-> (Product (Ratio Word) -> Ratio Word)
-> Product (Ratio Word)
-> Product (Ratio Word)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word -> Ratio Word
forall a. Fractional a => a -> a
Prelude.recip (Ratio Word -> Ratio Word)
-> (Product (Ratio Word) -> Ratio Word)
-> Product (Ratio Word)
-> Ratio Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Word) -> Ratio Word
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Word8)) where
invert :: Product (Ratio Word8) -> Product (Ratio Word8)
invert = Ratio Word8 -> Product (Ratio Word8)
forall a. a -> Product a
Product (Ratio Word8 -> Product (Ratio Word8))
-> (Product (Ratio Word8) -> Ratio Word8)
-> Product (Ratio Word8)
-> Product (Ratio Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word8 -> Ratio Word8
forall a. Fractional a => a -> a
Prelude.recip (Ratio Word8 -> Ratio Word8)
-> (Product (Ratio Word8) -> Ratio Word8)
-> Product (Ratio Word8)
-> Ratio Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Word8) -> Ratio Word8
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Word16)) where
invert :: Product (Ratio Word16) -> Product (Ratio Word16)
invert = Ratio Word16 -> Product (Ratio Word16)
forall a. a -> Product a
Product (Ratio Word16 -> Product (Ratio Word16))
-> (Product (Ratio Word16) -> Ratio Word16)
-> Product (Ratio Word16)
-> Product (Ratio Word16)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word16 -> Ratio Word16
forall a. Fractional a => a -> a
Prelude.recip (Ratio Word16 -> Ratio Word16)
-> (Product (Ratio Word16) -> Ratio Word16)
-> Product (Ratio Word16)
-> Ratio Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Word16) -> Ratio Word16
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Word32)) where
invert :: Product (Ratio Word32) -> Product (Ratio Word32)
invert = Ratio Word32 -> Product (Ratio Word32)
forall a. a -> Product a
Product (Ratio Word32 -> Product (Ratio Word32))
-> (Product (Ratio Word32) -> Ratio Word32)
-> Product (Ratio Word32)
-> Product (Ratio Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word32 -> Ratio Word32
forall a. Fractional a => a -> a
Prelude.recip (Ratio Word32 -> Ratio Word32)
-> (Product (Ratio Word32) -> Ratio Word32)
-> Product (Ratio Word32)
-> Ratio Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Word32) -> Ratio Word32
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group (Product (Ratio Word64)) where
invert :: Product (Ratio Word64) -> Product (Ratio Word64)
invert = Ratio Word64 -> Product (Ratio Word64)
forall a. a -> Product a
Product (Ratio Word64 -> Product (Ratio Word64))
-> (Product (Ratio Word64) -> Ratio Word64)
-> Product (Ratio Word64)
-> Product (Ratio Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio Word64 -> Ratio Word64
forall a. Fractional a => a -> a
Prelude.recip (Ratio Word64 -> Ratio Word64)
-> (Product (Ratio Word64) -> Ratio Word64)
-> Product (Ratio Word64)
-> Ratio Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Product (Ratio Word64) -> Ratio Word64
forall a. Product a -> a
getProduct
{-# inline invert #-}
instance Group a => Group (Const a b) where
invert :: Const a b -> Const a b
invert = a -> Const a b
forall k a (b :: k). a -> Const a b
Const (a -> Const a b) -> (Const a b -> a) -> Const a b -> Const a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
forall a. Group a => a -> a
invert (a -> a) -> (Const a b -> a) -> Const a b -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Const a b -> a
forall a k (b :: k). Const a b -> a
getConst
{-# inline invert #-}
instance Group a => Group (Identity a) where
invert :: Identity a -> Identity a
invert = a -> Identity a
forall a. a -> Identity a
Identity (a -> Identity a) -> (Identity a -> a) -> Identity a -> Identity a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
forall a. Group a => a -> a
invert (a -> a) -> (Identity a -> a) -> Identity a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity a -> a
forall a. Identity a -> a
runIdentity
{-# inline invert #-}
instance Group Ordering where
invert :: Ordering -> Ordering
invert Ordering
LT = Ordering
GT
invert Ordering
EQ = Ordering
EQ
invert Ordering
GT = Ordering
LT
{-# inline invert #-}
instance (Group a, Group b) => Group (a,b) where
invert :: (a, b) -> (a, b)
invert ~(a
a,b
b) = (a -> a
forall a. Group a => a -> a
invert a
a, b -> b
forall a. Group a => a -> a
invert b
b)
{-# inline invert #-}
instance Group a => Group (Proxy a) where
invert :: Proxy a -> Proxy a
invert Proxy a
_ = Proxy a
forall k (t :: k). Proxy t
Proxy
instance (Group a, Group b, Group c) => Group (a,b,c) where
invert :: (a, b, c) -> (a, b, c)
invert ~(a
a,b
b,c
c) = (a -> a
forall a. Group a => a -> a
invert a
a, b -> b
forall a. Group a => a -> a
invert b
b, c -> c
forall a. Group a => a -> a
invert c
c)
{-# inline invert #-}
instance (Group a, Group b, Group c, Group d) => Group (a,b,c,d) where
invert :: (a, b, c, d) -> (a, b, c, d)
invert ~(a
a,b
b,c
c,d
d) = (a -> a
forall a. Group a => a -> a
invert a
a, b -> b
forall a. Group a => a -> a
invert b
b, c -> c
forall a. Group a => a -> a
invert c
c, d -> d
forall a. Group a => a -> a
invert d
d)
{-# inline invert #-}
instance (Group a, Group b, Group c, Group d, Group e) => Group (a,b,c,d,e) where
invert :: (a, b, c, d, e) -> (a, b, c, d, e)
invert ~(a
a,b
b,c
c,d
d,e
e) = (a -> a
forall a. Group a => a -> a
invert a
a, b -> b
forall a. Group a => a -> a
invert b
b, c -> c
forall a. Group a => a -> a
invert c
c, d -> d
forall a. Group a => a -> a
invert d
d, e -> e
forall a. Group a => a -> a
invert e
e)
{-# inline invert #-}
#if MIN_VERSION_base(4,12,0)
instance (Group (f a), Group (g a)) => Group ((f :*: g) a) where
invert :: (:*:) f g a -> (:*:) f g a
invert (f a
f :*: g a
g) = f a -> f a
forall a. Group a => a -> a
invert f a
f f a -> g a -> (:*:) f g a
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g a -> g a
forall a. Group a => a -> a
invert g a
g
instance Group (f (g a)) => Group ((f :.: g) a) where
invert :: (:.:) f g a -> (:.:) f g a
invert (Comp1 f (g a)
fg) = (:.:) f g a -> (:.:) f g a
forall a. Group a => a -> a
invert (f (g a) -> (:.:) f g a
forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1).
f (g p) -> (:.:) f g p
Comp1 f (g a)
fg)
#endif
(><) :: Group a => a -> a -> a
a
a >< :: a -> a -> a
>< a
b = a
b a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a
{-# inline (><) #-}
conjugate :: Group a => a -> a -> a
conjugate :: a -> a -> a
conjugate a
g a
a = (a
g a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a) a -> a -> a
forall a. Group a => a -> a -> a
`minus` a
g
{-# inline conjugate #-}
unconjugate :: Group a => a -> a -> a
unconjugate :: a -> a -> a
unconjugate a
g a
a = a -> a
forall a. Group a => a -> a
invert a
g a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
g
pattern Conjugate :: Group a => (a,a) -> (a,a)
pattern $bConjugate :: (a, a) -> (a, a)
$mConjugate :: forall r a. Group a => (a, a) -> ((a, a) -> r) -> (Void# -> r) -> r
Conjugate t <- (\(g,a) -> (g, conjugate g a) -> t) where
Conjugate (a
g,a
a) = (a
g, a -> a -> a
forall a. Group a => a -> a -> a
unconjugate a
g a
a)
{-# complete Conjugate #-}
data Order = Infinite | Finite !Natural
deriving (Order -> Order -> Bool
(Order -> Order -> Bool) -> (Order -> Order -> Bool) -> Eq Order
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Order -> Order -> Bool
$c/= :: Order -> Order -> Bool
== :: Order -> Order -> Bool
$c== :: Order -> Order -> Bool
Eq, Int -> Order -> ShowS
[Order] -> ShowS
Order -> String
(Int -> Order -> ShowS)
-> (Order -> String) -> ([Order] -> ShowS) -> Show Order
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Order] -> ShowS
$cshowList :: [Order] -> ShowS
show :: Order -> String
$cshow :: Order -> String
showsPrec :: Int -> Order -> ShowS
$cshowsPrec :: Int -> Order -> ShowS
Show)
pattern Infinitary :: (Eq g, Group g) => g
pattern $mInfinitary :: forall r g.
(Eq g, Group g) =>
g -> (Void# -> r) -> (Void# -> r) -> r
Infinitary <- (order -> Infinite)
pattern Finitary :: (Eq g, Group g) => Natural -> g
pattern $mFinitary :: forall r g.
(Eq g, Group g) =>
g -> (Natural -> r) -> (Void# -> r) -> r
Finitary n <- (order -> Finite n)
order :: (Eq g, Group g) => g -> Order
order :: g -> Order
order g
a = Natural -> g -> Order
go Natural
0 g
a where
go :: Natural -> g -> Order
go !Natural
n g
g
| g
g g -> g -> Bool
forall a. Eq a => a -> a -> Bool
== g
forall a. Monoid a => a
mempty, Natural
n Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Natural
0 = Natural -> Order
Finite Natural
n
| g
g g -> g -> Bool
forall a. Eq a => a -> a -> Bool
== g
a, Natural
n Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Natural
0 = Order
Infinite
| Bool
otherwise = Natural -> g -> Order
go (Natural -> Natural
forall a. Enum a => a -> a
succ Natural
n) (g
g g -> g -> g
forall a. Semigroup a => a -> a -> a
<> g
a)
{-# inline order #-}
data Abelianizer a = Quot | Commuted a
deriving stock (Abelianizer a -> Abelianizer a -> Bool
(Abelianizer a -> Abelianizer a -> Bool)
-> (Abelianizer a -> Abelianizer a -> Bool) -> Eq (Abelianizer a)
forall a. Eq a => Abelianizer a -> Abelianizer a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Abelianizer a -> Abelianizer a -> Bool
$c/= :: forall a. Eq a => Abelianizer a -> Abelianizer a -> Bool
== :: Abelianizer a -> Abelianizer a -> Bool
$c== :: forall a. Eq a => Abelianizer a -> Abelianizer a -> Bool
Eq, Int -> Abelianizer a -> ShowS
[Abelianizer a] -> ShowS
Abelianizer a -> String
(Int -> Abelianizer a -> ShowS)
-> (Abelianizer a -> String)
-> ([Abelianizer a] -> ShowS)
-> Show (Abelianizer a)
forall a. Show a => Int -> Abelianizer a -> ShowS
forall a. Show a => [Abelianizer a] -> ShowS
forall a. Show a => Abelianizer a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Abelianizer a] -> ShowS
$cshowList :: forall a. Show a => [Abelianizer a] -> ShowS
show :: Abelianizer a -> String
$cshow :: forall a. Show a => Abelianizer a -> String
showsPrec :: Int -> Abelianizer a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Abelianizer a -> ShowS
Show)
instance Functor Abelianizer where
fmap :: (a -> b) -> Abelianizer a -> Abelianizer b
fmap a -> b
_ Abelianizer a
Quot = Abelianizer b
forall a. Abelianizer a
Quot
fmap a -> b
f (Commuted a
a) = b -> Abelianizer b
forall a. a -> Abelianizer a
Commuted (a -> b
f a
a)
instance Applicative Abelianizer where
pure :: a -> Abelianizer a
pure = a -> Abelianizer a
forall a. a -> Abelianizer a
Commuted
Abelianizer (a -> b)
Quot <*> :: Abelianizer (a -> b) -> Abelianizer a -> Abelianizer b
<*> Abelianizer a
_ = Abelianizer b
forall a. Abelianizer a
Quot
Abelianizer (a -> b)
_ <*> Abelianizer a
Quot = Abelianizer b
forall a. Abelianizer a
Quot
Commuted a -> b
f <*> Commuted a
a = b -> Abelianizer b
forall a. a -> Abelianizer a
Commuted (a -> b
f a
a)
instance Monad Abelianizer where
return :: a -> Abelianizer a
return = a -> Abelianizer a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
>> :: Abelianizer a -> Abelianizer b -> Abelianizer b
(>>) = Abelianizer a -> Abelianizer b -> Abelianizer b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
Abelianizer a
Quot >>= :: Abelianizer a -> (a -> Abelianizer b) -> Abelianizer b
>>= a -> Abelianizer b
_ = Abelianizer b
forall a. Abelianizer a
Quot
Commuted a
a >>= a -> Abelianizer b
f = a -> Abelianizer b
f a
a
instance Foldable Abelianizer where
foldMap :: (a -> m) -> Abelianizer a -> m
foldMap a -> m
_ Abelianizer a
Quot = m
forall a. Monoid a => a
mempty
foldMap a -> m
f (Commuted a
a) = a -> m
f a
a
instance Traversable Abelianizer where
traverse :: (a -> f b) -> Abelianizer a -> f (Abelianizer b)
traverse a -> f b
_ Abelianizer a
Quot = Abelianizer b -> f (Abelianizer b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Abelianizer b
forall a. Abelianizer a
Quot
traverse a -> f b
f (Commuted a
a) = b -> Abelianizer b
forall a. a -> Abelianizer a
Commuted (b -> Abelianizer b) -> f b -> f (Abelianizer b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a
instance Semigroup g => Semigroup (Abelianizer g) where
Abelianizer g
Quot <> :: Abelianizer g -> Abelianizer g -> Abelianizer g
<> Abelianizer g
t = Abelianizer g
t
Abelianizer g
t <> Abelianizer g
Quot = Abelianizer g
t
Commuted g
a <> Commuted g
b = g -> Abelianizer g
forall a. a -> Abelianizer a
Commuted (g
a g -> g -> g
forall a. Semigroup a => a -> a -> a
<> g
b)
instance Monoid g => Monoid (Abelianizer g) where
mempty :: Abelianizer g
mempty = g -> Abelianizer g
forall a. a -> Abelianizer a
Commuted g
forall a. Monoid a => a
mempty
instance (Eq g, Group g) => Group (Abelianizer g) where
invert :: Abelianizer g -> Abelianizer g
invert Abelianizer g
Quot = Abelianizer g
forall a. Abelianizer a
Quot
invert (Commuted g
a) = g -> Abelianizer g
forall a. a -> Abelianizer a
Commuted (g -> g
forall a. Group a => a -> a
invert g
a)
commutate :: Group g => g -> g -> g
commutate :: g -> g -> g
commutate g
g g
g' = g
g g -> g -> g
forall a. Semigroup a => a -> a -> a
<> g
g' g -> g -> g
forall a. Semigroup a => a -> a -> a
<> g -> g
forall a. Group a => a -> a
invert g
g g -> g -> g
forall a. Semigroup a => a -> a -> a
<> g -> g
forall a. Group a => a -> a
invert g
g'
{-# inline commutate #-}
abelianize :: (Eq g, Group g) => g -> g -> Abelianizer g
abelianize :: g -> g -> Abelianizer g
abelianize g
g g
g'
| g
x g -> g -> Bool
forall a. Eq a => a -> a -> Bool
== g
forall a. Monoid a => a
mempty = Abelianizer g
forall a. Abelianizer a
Quot
| Bool
otherwise = g -> Abelianizer g
forall a. a -> Abelianizer a
Commuted g
x
where
x :: g
x = g -> g -> g
forall a. Group a => a -> a -> a
commutate g
g g
g'
{-# inline abelianize #-}
pattern Abelianized :: (Eq g, Group g) => g -> (g,g)
pattern $mAbelianized :: forall r g.
(Eq g, Group g) =>
(g, g) -> (g -> r) -> (Void# -> r) -> r
Abelianized x <- (uncurry abelianize -> Commuted x)
pattern Quotiented :: (Eq g, Group g) => (g,g)
pattern $mQuotiented :: forall r g.
(Eq g, Group g) =>
(g, g) -> (Void# -> r) -> (Void# -> r) -> r
Quotiented <- (uncurry abelianize -> Quot)
class Group a => AbelianGroup a
instance AbelianGroup ()
instance AbelianGroup b => AbelianGroup (a -> b)
instance AbelianGroup a => AbelianGroup (Dual a)
instance AbelianGroup Any
instance AbelianGroup All
instance AbelianGroup (Sum Integer)
instance AbelianGroup (Sum Int)
instance AbelianGroup (Sum Int8)
instance AbelianGroup (Sum Int16)
instance AbelianGroup (Sum Int32)
instance AbelianGroup (Sum Int64)
instance AbelianGroup (Sum Word)
instance AbelianGroup (Sum Word8)
instance AbelianGroup (Sum Word16)
instance AbelianGroup (Sum Word32)
instance AbelianGroup (Sum Word64)
instance AbelianGroup (Sum (Ratio Integer))
instance AbelianGroup (Sum (Ratio Int))
instance AbelianGroup (Sum (Ratio Int8))
instance AbelianGroup (Sum (Ratio Int16))
instance AbelianGroup (Sum (Ratio Int32))
instance AbelianGroup (Sum (Ratio Int64))
instance AbelianGroup (Sum (Ratio Word))
instance AbelianGroup (Sum (Ratio Word8))
instance AbelianGroup (Sum (Ratio Word16))
instance AbelianGroup (Sum (Ratio Word32))
instance AbelianGroup (Sum (Ratio Word64))
instance AbelianGroup (Product (Ratio Integer))
instance AbelianGroup (Product (Ratio Int))
instance AbelianGroup (Product (Ratio Int8))
instance AbelianGroup (Product (Ratio Int16))
instance AbelianGroup (Product (Ratio Int32))
instance AbelianGroup (Product (Ratio Int64))
instance AbelianGroup (Product (Ratio Word))
instance AbelianGroup (Product (Ratio Word8))
instance AbelianGroup (Product (Ratio Word16))
instance AbelianGroup (Product (Ratio Word32))
instance AbelianGroup (Product (Ratio Word64))
instance AbelianGroup (Product (Ratio Natural))
instance AbelianGroup a => AbelianGroup (Const a b)
instance AbelianGroup a => AbelianGroup (Identity a)
instance AbelianGroup a => AbelianGroup (Proxy a)
instance AbelianGroup Ordering
instance (AbelianGroup a, AbelianGroup b) => AbelianGroup (a,b)
instance (AbelianGroup a, AbelianGroup b, AbelianGroup c) => AbelianGroup (a,b,c)
instance (AbelianGroup a, AbelianGroup b, AbelianGroup c, AbelianGroup d) => AbelianGroup (a,b,c,d)
instance (AbelianGroup a, AbelianGroup b, AbelianGroup c, AbelianGroup d, AbelianGroup e) => AbelianGroup (a,b,c,d,e)
instance AbelianGroup a => AbelianGroup (Down a)
instance AbelianGroup a => AbelianGroup (Endo a)
#if MIN_VERSION_base(4,12,0)
instance (AbelianGroup (f a), AbelianGroup (g a)) => AbelianGroup ((f :*: g) a)
instance AbelianGroup (f (g a)) => AbelianGroup ((f :.: g) a)
#endif
#if __GLASGOW_HASKELL__ > 804
instance AbelianGroup (Equivalence a)
instance AbelianGroup (Comparison a)
instance AbelianGroup (Predicate a)
instance AbelianGroup a => AbelianGroup (Op a b)
#endif
instance (Eq a, AbelianGroup a) => AbelianGroup (Abelianizer a)