module Basement.Numerical.Multiplicative
( Multiplicative(..)
, IDivisible(..)
, Divisible(..)
, recip
) where
import Basement.Compat.Base
import Basement.Compat.Natural
import Basement.Numerical.Number
import Basement.Numerical.Additive
import Basement.Types.Word128 (Word128)
import Basement.Types.Word256 (Word256)
import qualified Basement.Types.Word128 as Word128
import qualified Basement.Types.Word256 as Word256
import qualified Prelude
class Multiplicative a where
midentity :: a
(*) :: a -> a -> a
(^) :: (IsNatural n, IDivisible n) => a -> n -> a
(^) = power
class (Additive a, Multiplicative a) => IDivisible a where
div :: a -> a -> a
div a b = fst $ divMod a b
mod :: a -> a -> a
mod a b = snd $ divMod a b
divMod :: a -> a -> (a, a)
divMod a b = (div a b, mod a b)
class Multiplicative a => Divisible a where
(/) :: a -> a -> a
infixl 7 *, /
infixr 8 ^
instance Multiplicative Integer where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Int where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Int8 where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Int16 where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Int32 where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Int64 where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Natural where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Word where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Word8 where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Word16 where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Word32 where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Word64 where
midentity = 1
(*) = (Prelude.*)
instance Multiplicative Word128 where
midentity = 1
(*) = (Word128.*)
instance Multiplicative Word256 where
midentity = 1
(*) = (Word256.*)
instance Multiplicative Prelude.Float where
midentity = 1.0
(*) = (Prelude.*)
instance Multiplicative Prelude.Double where
midentity = 1.0
(*) = (Prelude.*)
instance Multiplicative Prelude.Rational where
midentity = 1.0
(*) = (Prelude.*)
instance IDivisible Integer where
div = Prelude.div
mod = Prelude.mod
instance IDivisible Int where
div = Prelude.div
mod = Prelude.mod
instance IDivisible Int8 where
div = Prelude.div
mod = Prelude.mod
instance IDivisible Int16 where
div = Prelude.div
mod = Prelude.mod
instance IDivisible Int32 where
div = Prelude.div
mod = Prelude.mod
instance IDivisible Int64 where
div = Prelude.div
mod = Prelude.mod
instance IDivisible Natural where
div = Prelude.quot
mod = Prelude.rem
instance IDivisible Word where
div = Prelude.quot
mod = Prelude.rem
instance IDivisible Word8 where
div = Prelude.quot
mod = Prelude.rem
instance IDivisible Word16 where
div = Prelude.quot
mod = Prelude.rem
instance IDivisible Word32 where
div = Prelude.quot
mod = Prelude.rem
instance IDivisible Word64 where
div = Prelude.quot
mod = Prelude.rem
instance IDivisible Word128 where
div = Word128.quot
mod = Word128.rem
instance IDivisible Word256 where
div = Word256.quot
mod = Word256.rem
instance Divisible Prelude.Rational where
(/) = (Prelude./)
instance Divisible Float where
(/) = (Prelude./)
instance Divisible Double where
(/) = (Prelude./)
recip :: Divisible a => a -> a
recip x = midentity / x
power :: (IsNatural n, IDivisible n, Multiplicative a) => a -> n -> a
power a n
| n == 0 = midentity
| otherwise = squaring midentity a n
where
squaring y x i
| i == 0 = y
| i == 1 = x * y
| even i = squaring y (x*x) (i`div`2)
| otherwise = squaring (x*y) (x*x) (pred i`div` 2)
even :: (IDivisible n, IsIntegral n) => n -> Bool
even n = (n `mod` 2) == 0