{-# LANGUAGE RebindableSyntax #-}
module Algebra.Ring (
C,
(*),
one,
fromInteger,
(^), sqr,
product, product1, scalarProduct,
propAssociative,
propLeftDistributive,
propRightDistributive,
propLeftIdentity,
propRightIdentity,
propPowerCascade,
propPowerProduct,
propPowerDistributive,
propCommutative,
) where
import qualified Algebra.Additive as Additive
import qualified Algebra.Laws as Laws
import Algebra.Additive(zero, (+), negate, sum)
import Data.Function.HT (powerAssociative, )
import NumericPrelude.List (zipWithChecked, )
import Test.QuickCheck ((==>), Property)
import Data.Int (Int, Int8, Int16, Int32, Int64, )
import Data.Word (Word, Word8, Word16, Word32, Word64, )
import NumericPrelude.Base
import Prelude (Integer, Float, Double, )
import qualified Data.Complex as Complex98
import qualified Data.Ratio as Ratio98
import qualified Prelude as P
infixl 7 *
infixr 8 ^
class (Additive.C a) => C a where
{-# MINIMAL (*), (one | fromInteger) #-}
(*) :: a -> a -> a
one :: a
fromInteger :: Integer -> a
(^) :: a -> Integer -> a
{-# INLINE fromInteger #-}
fromInteger Integer
n = if Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0
then (a -> a -> a) -> a -> a -> Integer -> a
forall a. (a -> a -> a) -> a -> a -> Integer -> a
powerAssociative a -> a -> a
forall a. C a => a -> a -> a
(+) a
forall a. C a => a
zero (a -> a
forall a. C a => a -> a
negate a
forall a. C a => a
one) (Integer -> Integer
forall a. C a => a -> a
negate Integer
n)
else (a -> a -> a) -> a -> a -> Integer -> a
forall a. (a -> a -> a) -> a -> a -> Integer -> a
powerAssociative a -> a -> a
forall a. C a => a -> a -> a
(+) a
forall a. C a => a
zero a
forall a. C a => a
one Integer
n
{-# INLINE (^) #-}
a
a ^ Integer
n = if Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
forall a. C a => a
zero
then (a -> a -> a) -> a -> a -> Integer -> a
forall a. (a -> a -> a) -> a -> a -> Integer -> a
powerAssociative a -> a -> a
forall a. C a => a -> a -> a
(*) a
forall a. C a => a
one a
a Integer
n
else [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"(^): Illegal negative exponent"
{-# INLINE one #-}
one = Integer -> a
forall a. C a => Integer -> a
fromInteger Integer
1
sqr :: C a => a -> a
sqr :: a -> a
sqr a
x = a
xa -> a -> a
forall a. C a => a -> a -> a
*a
x
product :: (C a) => [a] -> a
product :: [a] -> a
product = (a -> a -> a) -> a -> [a] -> a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl a -> a -> a
forall a. C a => a -> a -> a
(*) a
forall a. C a => a
one
product1 :: (C a) => [a] -> a
product1 :: [a] -> a
product1 = (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 a -> a -> a
forall a. C a => a -> a -> a
(*)
scalarProduct :: C a => [a] -> [a] -> a
scalarProduct :: [a] -> [a] -> a
scalarProduct [a]
as [a]
bs = [a] -> a
forall a. C a => [a] -> a
sum ((a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWithChecked a -> a -> a
forall a. C a => a -> a -> a
(*) [a]
as [a]
bs)
instance C Integer where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Integer
one = Integer -> Integer
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Integer
fromInteger = Integer -> Integer
forall a. Num a => Integer -> a
P.fromInteger
* :: Integer -> Integer -> Integer
(*) = Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(P.*)
instance C Float where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Float
one = Integer -> Float
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Float
fromInteger = Integer -> Float
forall a. Num a => Integer -> a
P.fromInteger
* :: Float -> Float -> Float
(*) = Float -> Float -> Float
forall a. Num a => a -> a -> a
(P.*)
instance C Double where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Double
one = Integer -> Double
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Double
fromInteger = Integer -> Double
forall a. Num a => Integer -> a
P.fromInteger
* :: Double -> Double -> Double
(*) = Double -> Double -> Double
forall a. Num a => a -> a -> a
(P.*)
instance C Int where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Int
one = Integer -> Int
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Int
fromInteger = Integer -> Int
forall a. Num a => Integer -> a
P.fromInteger
* :: Int -> Int -> Int
(*) = Int -> Int -> Int
forall a. Num a => a -> a -> a
(P.*)
instance C Int8 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Int8
one = Integer -> Int8
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Int8
fromInteger = Integer -> Int8
forall a. Num a => Integer -> a
P.fromInteger
* :: Int8 -> Int8 -> Int8
(*) = Int8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
(P.*)
instance C Int16 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Int16
one = Integer -> Int16
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Int16
fromInteger = Integer -> Int16
forall a. Num a => Integer -> a
P.fromInteger
* :: Int16 -> Int16 -> Int16
(*) = Int16 -> Int16 -> Int16
forall a. Num a => a -> a -> a
(P.*)
instance C Int32 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Int32
one = Integer -> Int32
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Int32
fromInteger = Integer -> Int32
forall a. Num a => Integer -> a
P.fromInteger
* :: Int32 -> Int32 -> Int32
(*) = Int32 -> Int32 -> Int32
forall a. Num a => a -> a -> a
(P.*)
instance C Int64 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Int64
one = Integer -> Int64
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Int64
fromInteger = Integer -> Int64
forall a. Num a => Integer -> a
P.fromInteger
* :: Int64 -> Int64 -> Int64
(*) = Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
(P.*)
instance C Word where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Word
one = Integer -> Word
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Word
fromInteger = Integer -> Word
forall a. Num a => Integer -> a
P.fromInteger
* :: Word -> Word -> Word
(*) = Word -> Word -> Word
forall a. Num a => a -> a -> a
(P.*)
instance C Word8 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Word8
one = Integer -> Word8
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Word8
fromInteger = Integer -> Word8
forall a. Num a => Integer -> a
P.fromInteger
* :: Word8 -> Word8 -> Word8
(*) = Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
(P.*)
instance C Word16 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Word16
one = Integer -> Word16
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Word16
fromInteger = Integer -> Word16
forall a. Num a => Integer -> a
P.fromInteger
* :: Word16 -> Word16 -> Word16
(*) = Word16 -> Word16 -> Word16
forall a. Num a => a -> a -> a
(P.*)
instance C Word32 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Word32
one = Integer -> Word32
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Word32
fromInteger = Integer -> Word32
forall a. Num a => Integer -> a
P.fromInteger
* :: Word32 -> Word32 -> Word32
(*) = Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
(P.*)
instance C Word64 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Word64
one = Integer -> Word64
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Word64
fromInteger = Integer -> Word64
forall a. Num a => Integer -> a
P.fromInteger
* :: Word64 -> Word64 -> Word64
(*) = Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
(P.*)
propAssociative :: (Eq a, C a) => a -> a -> a -> Bool
propLeftDistributive :: (Eq a, C a) => a -> a -> a -> Bool
propRightDistributive :: (Eq a, C a) => a -> a -> a -> Bool
propLeftIdentity :: (Eq a, C a) => a -> Bool
propRightIdentity :: (Eq a, C a) => a -> Bool
propAssociative :: a -> a -> a -> Bool
propAssociative = (a -> a -> a) -> a -> a -> a -> Bool
forall a. Eq a => (a -> a -> a) -> a -> a -> a -> Bool
Laws.associative a -> a -> a
forall a. C a => a -> a -> a
(*)
propLeftDistributive :: a -> a -> a -> Bool
propLeftDistributive = (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool
forall a b.
Eq a =>
(a -> b -> a) -> (a -> a -> a) -> b -> a -> a -> Bool
Laws.leftDistributive a -> a -> a
forall a. C a => a -> a -> a
(*) a -> a -> a
forall a. C a => a -> a -> a
(+)
propRightDistributive :: a -> a -> a -> Bool
propRightDistributive = (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool
forall a b.
Eq a =>
(b -> a -> a) -> (a -> a -> a) -> b -> a -> a -> Bool
Laws.rightDistributive a -> a -> a
forall a. C a => a -> a -> a
(*) a -> a -> a
forall a. C a => a -> a -> a
(+)
propLeftIdentity :: a -> Bool
propLeftIdentity = (a -> a -> a) -> a -> a -> Bool
forall a b. Eq a => (b -> a -> a) -> b -> a -> Bool
Laws.leftIdentity a -> a -> a
forall a. C a => a -> a -> a
(*) a
forall a. C a => a
one
propRightIdentity :: a -> Bool
propRightIdentity = (a -> a -> a) -> a -> a -> Bool
forall a b. Eq a => (a -> b -> a) -> b -> a -> Bool
Laws.rightIdentity a -> a -> a
forall a. C a => a -> a -> a
(*) a
forall a. C a => a
one
propPowerCascade :: (Eq a, C a) => a -> Integer -> Integer -> Property
propPowerProduct :: (Eq a, C a) => a -> Integer -> Integer -> Property
propPowerDistributive :: (Eq a, C a) => Integer -> a -> a -> Property
propPowerCascade :: a -> Integer -> Integer -> Property
propPowerCascade a
x Integer
i Integer
j = Integer
iInteger -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>=Integer
0 Bool -> Bool -> Bool
&& Integer
jInteger -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>=Integer
0 Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (Integer -> Integer -> Integer)
-> (a -> Integer -> a) -> a -> Integer -> Integer -> Bool
forall a b.
Eq a =>
(b -> b -> b) -> (a -> b -> a) -> a -> b -> b -> Bool
Laws.rightCascade Integer -> Integer -> Integer
forall a. C a => a -> a -> a
(*) a -> Integer -> a
forall a. C a => a -> Integer -> a
(^) a
x Integer
i Integer
j
propPowerProduct :: a -> Integer -> Integer -> Property
propPowerProduct a
x Integer
i Integer
j = Integer
iInteger -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>=Integer
0 Bool -> Bool -> Bool
&& Integer
jInteger -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>=Integer
0 Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (Integer -> a)
-> (Integer -> Integer -> Integer)
-> (a -> a -> a)
-> Integer
-> Integer
-> Bool
forall a b.
Eq a =>
(b -> a) -> (b -> b -> b) -> (a -> a -> a) -> b -> b -> Bool
Laws.homomorphism (a
xa -> Integer -> a
forall a. C a => a -> Integer -> a
^) Integer -> Integer -> Integer
forall a. C a => a -> a -> a
(+) a -> a -> a
forall a. C a => a -> a -> a
(*) Integer
i Integer
j
propPowerDistributive :: Integer -> a -> a -> Property
propPowerDistributive Integer
i a
x a
y = Integer
iInteger -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>=Integer
0 Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> (a -> Integer -> a) -> (a -> a -> a) -> Integer -> a -> a -> Bool
forall a b.
Eq a =>
(a -> b -> a) -> (a -> a -> a) -> b -> a -> a -> Bool
Laws.leftDistributive a -> Integer -> a
forall a. C a => a -> Integer -> a
(^) a -> a -> a
forall a. C a => a -> a -> a
(*) Integer
i a
x a
y
propCommutative :: (Eq a, C a) => a -> a -> Bool
propCommutative :: a -> a -> Bool
propCommutative = (a -> a -> a) -> a -> a -> Bool
forall a b. Eq a => (b -> b -> a) -> b -> b -> Bool
Laws.commutative a -> a -> a
forall a. C a => a -> a -> a
(*)
instance (P.Integral a) => C (Ratio98.Ratio a) where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Ratio a
one = Integer -> Ratio a
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Ratio a
fromInteger = Integer -> Ratio a
forall a. Num a => Integer -> a
P.fromInteger
* :: Ratio a -> Ratio a -> Ratio a
(*) = Ratio a -> Ratio a -> Ratio a
forall a. Num a => a -> a -> a
(P.*)
instance (P.RealFloat a) => C (Complex98.Complex a) where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one :: Complex a
one = Integer -> Complex a
forall a. Num a => Integer -> a
P.fromInteger Integer
1
fromInteger :: Integer -> Complex a
fromInteger = Integer -> Complex a
forall a. Num a => Integer -> a
P.fromInteger
* :: Complex a -> Complex a -> Complex a
(*) = Complex a -> Complex a -> Complex a
forall a. Num a => a -> a -> a
(P.*)