module Algebra.Module where
import qualified Number.Ratio as Ratio
import qualified Algebra.PrincipalIdealDomain as PID
import qualified Algebra.Ring as Ring
import qualified Algebra.Additive as Additive
import qualified Algebra.ToInteger as ToInteger
import qualified Algebra.Laws as Laws
import Algebra.Ring ((*), fromInteger, )
import Algebra.Additive ((+), zero, sum, )
import qualified NumericPrelude.Elementwise as Elem
import Control.Applicative (Applicative(pure, (<*>)), )
import qualified Data.Complex as Complex98
import Data.Function.HT (powerAssociative, )
import Data.List (map, zipWith, )
import Data.Tuple.HT (fst3, snd3, thd3, )
import Data.Tuple (fst, snd, )
import qualified Prelude as P
import Prelude((.), Eq, Bool, Int, Integer, Float, Double, ($), )
infixr 7 *>
class (Ring.C a, Additive.C v) => C a v where
(*>) :: a -> v -> v
(<*>.*>) ::
(C a x) =>
Elem.T (a,v) (x -> c) -> (v -> x) -> Elem.T (a,v) c
(<*>.*>) f acc =
f <*> Elem.element (\(a,v) -> a *> acc v)
instance C Float Float where
(*>) = (*)
instance C Double Double where
(*>) = (*)
instance C Int Int where
(*>) = (*)
instance C Integer Integer where
(*>) = (*)
instance (PID.C a) => C (Ratio.T a) (Ratio.T a) where
(*>) = (*)
instance (PID.C a) => C Integer (Ratio.T a) where
x *> y = fromInteger x * y
instance (C a b0, C a b1) => C a (b0, b1) where
(*>) = Elem.run2 $ pure (,) <*>.*> fst <*>.*> snd
instance (C a b0, C a b1, C a b2) => C a (b0, b1, b2) where
(*>) = Elem.run2 $ pure (,,) <*>.*> fst3 <*>.*> snd3 <*>.*> thd3
instance (C a v) => C a [v] where
(*>) = map . (*>)
instance (C a v) => C a (c -> v) where
(*>) s f = (*>) s . f
instance (C a b, P.RealFloat b) => C a (Complex98.Complex b) where
s *> (x Complex98.:+ y) = (s *> x) Complex98.:+ (s *> y)
linearComb :: C a v => [a] -> [v] -> v
linearComb c = sum . zipWith (*>) c
integerMultiply :: (ToInteger.C a, Additive.C v) => a -> v -> v
integerMultiply a v =
powerAssociative (+) zero v (ToInteger.toInteger a)
propCascade :: (Eq v, C a v) => v -> a -> a -> Bool
propCascade = Laws.leftCascade (*) (*>)
propRightDistributive :: (Eq v, C a v) => a -> v -> v -> Bool
propRightDistributive = Laws.rightDistributive (*>) (+)
propLeftDistributive :: (Eq v, C a v) => v -> a -> a -> Bool
propLeftDistributive x = Laws.homomorphism (*>x) (+) (+)