module Polynomial.Basic where
polyeval :: Num a => [a] -> a -> a
polyeval [] _ = 0
polyeval (p:ps) x = p + x * polyeval ps x
polyadd :: Num a => [a] -> [a] -> [a]
polyadd [] ys = ys
polyadd xs [] = xs
polyadd (x:xs) (y:ys) = (x+y) : polyadd xs ys
polyAddScalar :: Num a => a -> [a] -> [a]
polyAddScalar c [] = [c]
polyAddScalar c (x:xs) = (c+x):xs
polysub :: Num a => [a] -> [a] -> [a]
polysub [] ys = map negate ys
polysub xs [] = xs
polysub (x:xs) (y:ys) = (x-y) : polysub xs ys
polyscale :: Num a => a -> [a] -> [a]
polyscale a x = map (a*) x
polymult :: Num a => [a] -> [a] -> [a]
polymult ys =
foldr (\x acc -> polyadd (polyscale x ys) (0 : acc)) []
polymultAlt :: Num a => [a] -> [a] -> [a]
polymultAlt _ [] = []
polymultAlt ys (x:xs) = polyadd (polyscale x ys) (0 : polymult ys xs)
polydiv :: Fractional a => [a] -> [a] -> [a]
polydiv x0 y0 = reverse $ polydiv' (reverse x0) (reverse y0)
where polydiv' (x:xs) y
| length (x:xs) < length y = []
| otherwise = z : (polydiv' (tail (polysub (x:xs) (polymult [z] y))) y)
where z = x / head y
polydiv' [] _ = []
polymod :: Fractional a => [a] -> [a] -> [a]
polymod x0 y0 = reverse $ polymod' (reverse x0) (reverse y0)
where polymod' (x:xs) y
| length (x:xs) < length y = (x:xs)
| otherwise = polymod' (tail (polysub (x:xs) (polymult [z] y))) y
where z = x / head y
polymod' [] _ = []
polypow :: (Num a, Integral b) => [a] -> b -> [a]
polypow _ 0 = [ 1 ]
polypow x 1 = x
polypow x n | even n = xSqr
| otherwise = polymult x xSqr
where xSqr = polymult x2 x2
x2 = polypow x (n `div` 2)
polysubst :: Num a => [a] -> [a] -> [a]
polysubst ws = foldr (\x -> polyAddScalar x . polymult ws) []
polysubstAlt :: Num a => [a] -> [a] -> [a]
polysubstAlt w0 x0 = foldr polyadd [0] (polysubst' 0 w0 x0)
where polysubst' _ _ [] = []
polysubst' n w (x:xs) = polyscale x (polypow w (n::Int)) : polysubst' (n+1) w xs
polyPolySubst :: Num a => [a] -> [[a]] -> [a]
polyPolySubst ws = foldr (\x -> polyadd x . polymult ws) []
polyderiv :: Num a => [a] -> [a]
polyderiv [] = []
polyderiv (_:xs0) = polyderiv' 1 xs0
where polyderiv' _ [] = []
polyderiv' n (x:xs) = n * x : polyderiv' (n+1) xs
polyinteg :: Fractional a => [a] -> a -> [a]
polyinteg x0 c = c : polyinteg' 1 x0
where polyinteg' _ [] = []
polyinteg' n (x:xs) = x / n : polyinteg' (n+1) xs
roots2poly :: Num a => [a] -> [a]
roots2poly [] = [1]
roots2poly (r:rs) = polymult [-r, 1] (roots2poly rs)