> module PowerSeries where > import NumPrelude > import qualified Prelude as P > import VectorSpace > import Prelude hiding ( > Int, Integer, Float, Double, Rational, Num(..), Real(..), > Integral(..), Fractional(..), Floating(..), RealFrac(..), > RealFloat(..), subtract, even, odd, > gcd, lcm, (^), (^^)) Power series, either finite or unbounded. (zipWith does exactly the right thing to make it work almost transparently.) > newtype PowerSeries a = PS [a] deriving (Eq, Ord, Show) > stripPS (PS l) = l > truncatePS :: Int -> PowerSeries a -> PowerSeries a > truncatePS n (PS a) = PS (take n a) Note that the derived instances only make sense for finite series. > instance (Additive a) => Additive (PowerSeries a) where > negate (PS l) = PS (map negate l) > (PS a) + (PS b) = PS (zipWith (+) a b) > zero = PS (repeat zero) > > instance (Num a) => Num (PowerSeries a) where > one = PS (one:repeat zero) > fromInteger n = PS (fromInteger n : repeat zero) > PS (a:as) * PS (b:bs) = PS ((a*b):stripPS (a *> PS bs + PS as*PS (b:bs))) > PS _ * PS _ = PS [] > > instance (Num a) => Module a (PowerSeries a) where > a *> (PS bs) = PS (map (a *) bs) It would be nice to also provide: instance (Module a b) => Module a (PowerSeries b) where a *> (PS bs) = PS (map (a *>) bs) maybe with instance (Num a) => Module a a where (*>) = (*) > instance (Integral a) => Integral (PowerSeries a) where > divMod a b = (\(x,y)-> (PS x, PS y)) (unzip (aux a b)) > where aux (PS (a:as)) (PS (b:bs)) = > let (d,m) = divMod a b in > (d,m):aux (PS as - d *> (PS bs)) (PS (b:bs)) > aux _ _ = []