{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module MathObj.MultiVarPolynomial
(
T(..)
, fromMonomials
, lift0
, lift1
, lift2
, x
, constant
, compose
, merge
) where
import qualified Algebra.Additive as Additive
import qualified Algebra.Ring as Ring
import qualified Algebra.ZeroTestable as ZeroTestable
import qualified Algebra.Differential as Differential
import qualified MathObj.Monomial as Mon
import qualified Data.Map as M
import NumericPrelude
newtype T a = Cons [Mon.T a]
instance (ZeroTestable.C a, Ring.C a, Ord a, Show a) => Show (T a) where
show (Cons []) = "0"
show (Cons (m:ms)) = show m ++ concatMap showMon ms
where showMon m | Mon.coeff m < zero = " - " ++ show (negate m)
| otherwise = " + " ++ show m
{-# INLINE fromMonomials #-}
fromMonomials :: [Mon.T a] -> T a
fromMonomials = lift0
{-# INLINE lift0 #-}
lift0 :: [Mon.T a] -> T a
lift0 = Cons
{-# INLINE lift1 #-}
lift1 :: ([Mon.T a] -> [Mon.T a]) -> (T a -> T a)
lift1 f (Cons xs) = Cons (f xs)
{-# INLINE lift2 #-}
lift2 :: ([Mon.T a] -> [Mon.T a] -> [Mon.T a]) -> (T a -> T a -> T a)
lift2 f (Cons xs) (Cons ys) = Cons (f xs ys)
x :: (Ring.C a) => Integer -> T a
x n = fromMonomials [Mon.x n]
constant :: a -> T a
constant a = fromMonomials [Mon.constant a]
add :: (Ord a, Additive.C a) => [a] -> [a] -> [a]
add xs ys = merge True (+) xs ys
merge :: Ord a => Bool -> (a -> a -> a) -> [a] -> [a] -> [a]
merge True _ [] ys = ys
merge False _ [] _ = []
merge True _ xs [] = xs
merge False _ _ [] = []
merge b f xxs@(x:xs) yys@(y:ys) | x < y = if' b (x:) id $ merge b f xs yys
| x > y = if' b (y:) id $ merge b f xxs ys
| otherwise = f x y : merge b f xs ys
where if' True x _ = x
if' False _ y = y
instance (Additive.C a, ZeroTestable.C a) => Additive.C (T a) where
zero = fromMonomials []
negate = lift1 $ map negate
(+) = lift2 add
mul :: (Ring.C a, Ord a) => [a] -> [a] -> [a]
mul [] _ = []
mul _ [] = []
mul (x:xs) (y:ys) = x*y : add (map (x*) ys) (mul xs (y:ys))
instance (Ring.C a, ZeroTestable.C a) => Ring.C (T a) where
fromInteger n = fromMonomials [fromInteger n]
(*) = lift2 mul
instance (ZeroTestable.C a, Ring.C a) => Differential.C (T a) where
differentiate = lift1 $ filter (not . isZero) . map Differential.differentiate
compose :: (Ring.C a, ZeroTestable.C a) => T a -> T a -> T a
compose (Cons []) _ = Cons []
compose (Cons (x:_)) (Cons []) = Cons [x]
compose (Cons xs) yys@(Cons (y:_))
| Mon.degree y == 0 && (not . isZero . Mon.coeff $ y)
= error $ "MultiVarPolynomial.compose: inner series must not have a constant term."
| otherwise = comp xs yys
comp :: (Ring.C a, ZeroTestable.C a) => [Mon.T a] -> T a -> T a
comp ms p = comp' zero ms
where
comp' part [] = part
comp' part (m:ms) = lift2 (++) done $ comp' (rest + substMon p m) ms
where (done,rest) = splitPoly ((< Mon.pDegree m) . Mon.pDegree) part
substMon :: (ZeroTestable.C a, Ring.C a) => T a -> Mon.T a -> T a
substMon poly m
= (constant (Mon.coeff m) *)
. M.foldrWithKey (\sub pow -> (*) (scalePoly sub poly ^pow)) one
$ Mon.powers m
scalePoly :: Integer -> T a -> T a
scalePoly n = lift1 $ map (Mon.scaleMon n)
splitPoly :: (Mon.T a -> Bool) -> T a -> (T a, T a)
splitPoly p (Cons xs) = (Cons ys, Cons zs)
where (ys, zs) = span p xs