module Data.Algebra.Module where
import Data.Ratio
import qualified Data.Map as M
import qualified Data.IntMap as IM
import Data.Algebra.Group
import Data.Algebra.Ring
class (Ring r, Group m) => Module r m where
(*^) :: r -> m -> m
instance Module Int Int where
(*^) = (*)
instance Module Integer Integer where
(*^) = (*)
instance Module Int Integer where
(*^) = (*) . fromIntegral
instance Integral a => Module Int (Ratio a) where
(*^) = (*) . fromIntegral
instance Integral a => Module Integer (Ratio a) where
(*^) = (*) . fromIntegral
instance Integral a => Module (Ratio a) (Ratio a) where
(*^) = (*)
instance Module Int Double where
(*^) = (*) . fromIntegral
instance Module Integer Double where
(*^) = (*) . fromIntegral
instance Integral a => Module (Ratio a) Double where
(*^) = (*) . realToFrac
instance Module Double Double where
(*^) = (*)
instance (Ord g, Group g, Ring r) => Module (GroupRing r g) (GroupRing r g) where
(*^) = (*#)
instance Module r m => Module r (a -> m) where
(*^) = fmap . (*^)
instance (Ord k, Module r m) => Module r (M.Map k m) where
(*^) = fmap . (*^)
instance Module r m => Module r (IM.IntMap m) where
(*^) = fmap . (*^)
instance (Module r m1, Module r m2) => Module r (m1, m2) where
r *^ (a, b) = (r *^ a, r *^ b)
instance (Module r m1, Module r m2, Module r m3) => Module r (m1, m2, m3) where
r *^ (a, b, c) = (r *^ a, r *^ b, r *^ c)
instance (Module r m1, Module r m2, Module r m3, Module r m4) => Module r (m1, m2, m3, m4) where
r *^ (a, b, c, d) = (r *^ a, r *^ b, r *^ c, r *^ d)
type LinFunc = M.Map
var :: (Ord v, Ring c) => v -> LinFunc v c
var v = M.singleton v one
(*&) :: (Ord v, Ring c) => c -> v -> LinFunc v c
c *& v = M.singleton v c
varSum :: (Ord v, Ring c) => [v] -> LinFunc v c
varSum vs = M.fromList [(v, one) | v <- vs]
combination :: Module r m => [(r, m)] -> m
combination xs = gsum [r *^ m | (r, m) <- xs]
linCombination :: (Ord v, Num r) => [(r, v)] -> LinFunc v r
linCombination xs = M.fromListWith (+) [(v, r) | (r, v) <- xs]
evalPoly :: (Module r m, Ring m) => Poly r -> m -> m
evalPoly f x = foldr (\ c z -> (c *^ one) ^+^ (x *# z)) zero f