{-# LANGUAGE NoImplicitPrelude #-}
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 n = if n < 0
then powerAssociative (+) zero (negate one) (negate n)
else powerAssociative (+) zero one n
{-# INLINE (^) #-}
a ^ n = if n >= zero
then powerAssociative (*) one a n
else error "(^): Illegal negative exponent"
{-# INLINE one #-}
one = fromInteger 1
sqr :: C a => a -> a
sqr x = x*x
product :: (C a) => [a] -> a
product = foldl (*) one
product1 :: (C a) => [a] -> a
product1 = foldl1 (*)
scalarProduct :: C a => [a] -> [a] -> a
scalarProduct as bs = sum (zipWithChecked (*) as bs)
instance C Integer where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Float where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Double where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Int where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Int8 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Int16 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Int32 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Int64 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Word where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Word8 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Word16 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Word32 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance C Word64 where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (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 = Laws.associative (*)
propLeftDistributive = Laws.leftDistributive (*) (+)
propRightDistributive = Laws.rightDistributive (*) (+)
propLeftIdentity = Laws.leftIdentity (*) one
propRightIdentity = Laws.rightIdentity (*) 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 x i j = i>=0 && j>=0 ==> Laws.rightCascade (*) (^) x i j
propPowerProduct x i j = i>=0 && j>=0 ==> Laws.homomorphism (x^) (+) (*) i j
propPowerDistributive i x y = i>=0 ==> Laws.leftDistributive (^) (*) i x y
propCommutative :: (Eq a, C a) => a -> a -> Bool
propCommutative = Laws.commutative (*)
instance (P.Integral a) => C (Ratio98.Ratio a) where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)
instance (P.RealFloat a) => C (Complex98.Complex a) where
{-# INLINE one #-}
{-# INLINE fromInteger #-}
{-# INLINE (*) #-}
one = P.fromInteger 1
fromInteger = P.fromInteger
(*) = (P.*)