{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Ring.Module -- Copyright : (c) Edward Kmett 2009 -- License : BSD-style -- Maintainer : ekmett@gmail.com -- Stability : experimental -- Portability : non-portable (MPTCs) -- -- Left- and right- modules over rings, semirings, and Seminearrings. -- To avoid a proliferation of classes. These only require that there -- be an addition and multiplication operation for the 'Ring' -- ----------------------------------------------------------------------------- module Data.Ring.Module ( module Data.Ring , LeftModule , (*.) , RightModule , (.*) , Module ) where import Data.Ring import Data.Monoid.Union -- import qualified Data.Monoid.Combinators as Monoid -- | @ (x * y) *. m = x * (y *. m) @ class (Monoid r, Multiplicative r, Monoid m) => LeftModule r m where (*.) :: r -> m -> m -- | @ (m .* x) * y = m .* (x * y) @ class (Monoid r, Multiplicative r, Monoid m) => RightModule r m where (.*) :: m -> r -> m -- | @ (x *. m) .* y = x *. (m .* y) @ class (LeftModule r m, RightModule r m) => Module r m instance (LeftModule r m, LeftModule r n) => LeftModule r (m,n) where r *. (m,n) = (r *. m, r *. n) instance (LeftModule r m, LeftModule r n, LeftModule r o) => LeftModule r (m,n,o) where r *. (m,n,o) = (r *. m, r *. n, r *. o) instance (LeftModule r m, LeftModule r n, LeftModule r o, LeftModule r p) => LeftModule r (m,n,o,p) where r *. (m,n,o,p) = (r *. m, r *. n, r *. o, r *. p) instance (LeftModule r m, LeftModule r n, LeftModule r o, LeftModule r p, LeftModule r q) => LeftModule r (m,n,o,p,q) where r *. (m,n,o,p,q) = (r *. m, r *. n, r *. o, r *. p, r *. q) instance (RightModule r m, RightModule r n) => RightModule r (m,n) where (m,n) .* r = (m .* r, n .* r) instance (RightModule r m, RightModule r n, RightModule r o) => RightModule r (m,n,o) where (m,n,o) .* r = (m .* r, n .* r, o .* r) instance (RightModule r m, RightModule r n, RightModule r o, RightModule r p ) => RightModule r (m,n,o,p) where (m,n,o,p) .* r = (m .* r, n .* r, o .* r, p .* r) instance (RightModule r m, RightModule r n, RightModule r o, RightModule r p, RightModule r q ) => RightModule r (m,n,o,p,q) where (m,n,o,p,q) .* r = (m .* r, n .* r, o .* r, p .* r, q .* r) instance (Module r m, Module r n) => Module r (m,n) instance (Module r m, Module r n, Module r o) => Module r (m,n,o) instance (Module r m, Module r n, Module r o, Module r p) => Module r (m,n,o,p) instance (Module r m, Module r n, Module r o, Module r p, Module r q) => Module r (m,n,o,p,q) -- we want an absorbing 0, for that we need a seminearring and a notion of equality instance (HasUnionWith f, Ord r, Eq r, RightSemiNearRing r) => LeftModule r (UnionWith f r) where r *. m | r == zero = zero | otherwise = fmap (r `times`) m instance (HasUnionWith f, Ord r, Eq r, RightSemiNearRing r) => RightModule r (UnionWith f r) where m .* r | r == zero = zero | otherwise = fmap (`times` r) m instance (HasUnionWith f, Ord r, Eq r, RightSemiNearRing r) => Module r (UnionWith f r) where