{-# LANGUAGE
BangPatterns, FlexibleContexts, FlexibleInstances, TypeSynonymInstances, TypeFamilies,
ConstraintKinds, KindSignatures
#-}
module Math.Algebra.Polynomial.FreeModule where
import Prelude hiding ( sum , product )
import Data.List hiding ( sum , product )
import Data.Monoid
import Data.Ratio
import Data.Maybe
import Data.Typeable
import Data.Proxy
import Control.Monad ( foldM )
import qualified Data.Map.Strict as Map
import Data.Map.Strict (Map)
import Data.Set (Set)
class PartialMonoid a where
pmUnit :: a
pmAdd :: a -> a -> Maybe a
pmSum :: [a] -> Maybe a
pmSum xs = case xs of { [] -> Just pmUnit ; (y:ys) -> foldM pmAdd y ys }
pmAdd x y = pmSum [x,y]
class (Ord (BaseF a)) => FreeModule a where
type BaseF a :: *
type CoeffF a :: *
toFreeModule :: a -> FreeMod (CoeffF a) (BaseF a)
fromFreeModule :: FreeMod (CoeffF a) (BaseF a) -> a
instance Ord b => FreeModule (FreeMod c b) where
type BaseF (FreeMod c b) = b
type CoeffF (FreeMod c b) = c
toFreeModule = id
fromFreeModule = id
newtype FreeMod coeff base = FreeMod { unFreeMod :: Map base coeff } deriving (Eq,Ord,Show)
type ZMod base = FreeMod Integer base
type QMod base = FreeMod Rational base
size :: FreeMod c b -> Int
size (FreeMod table) = Map.size table
supportList :: Ord b => FreeMod c b -> [b]
supportList (FreeMod table) = Map.keys table
supportSet :: Ord b => FreeMod c b -> Set b
supportSet (FreeMod table) = Map.keysSet table
instance (Monoid b, Ord b, Eq c, Num c) => Num (FreeMod c b) where
(+) = add
(-) = sub
negate = neg
(*) = mul
fromInteger = konst . fromInteger
abs = id
signum _ = konst 1
normalize :: (Ord b, Eq c, Num c) => FreeMod c b -> FreeMod c b
normalize = FreeMod . Map.filter (/=0) . unFreeMod
safeEq :: (Ord b, Eq b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> Bool
safeEq x y = normalize x == normalize y
zero :: FreeMod c b
zero = FreeMod $ Map.empty
isZero :: Ord b => FreeMod c b -> Bool
isZero (FreeMod mp) = Map.null mp
generator :: Num c => b -> FreeMod c b
generator x = FreeMod $ Map.singleton x 1
singleton :: (Ord b, Num c, Eq c) => b -> c -> FreeMod c b
singleton b c = FreeMod $ if c/=0
then Map.singleton b c
else Map.empty
fromList :: (Eq c, Num c, Ord b) => [(b,c)] -> FreeMod c b
fromList = FreeMod . Map.filter cond . Map.fromListWith (+) where
cond x = (x /= 0)
fromMap :: (Eq c, Num c, Ord b) => Map b c -> FreeMod c b
fromMap = FreeMod . Map.filter (/=0)
fromGeneratorSet :: (Ord b, Num c) => Set b -> FreeMod c b
fromGeneratorSet = FreeMod . Map.fromSet (const 1)
fromGeneratorList :: (Ord b, Eq c, Num c) => [b] -> FreeMod c b
fromGeneratorList bs = FreeMod $ foldl' f Map.empty bs where
f !old !b = Map.alter g b old
g !mb = case mb of
Nothing -> Just 1
Just k -> let k' = k+1
in if k' /= 0 then Just k' else Nothing
toList :: FreeMod c b -> [(b,c)]
toList = Map.toList . unFreeMod
coeffOf :: (Ord b, Num c) => b -> FreeMod c b -> c
coeffOf b (FreeMod x) = case Map.lookup b x of
Just c -> c
Nothing -> 0
findMaxTerm :: (Ord b) => FreeMod c b -> Maybe (b,c)
findMaxTerm (FreeMod m) = if Map.null m
then Nothing
else Just (Map.findMax m)
findMinTerm :: (Ord b) => FreeMod c b -> Maybe (b,c)
findMinTerm (FreeMod m) = if Map.null m
then Nothing
else Just (Map.findMin m)
neg :: Num c => FreeMod c b -> FreeMod c b
neg (FreeMod m) = FreeMod (Map.map negate m)
add :: (Ord b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> FreeMod c b
add (FreeMod m1) (FreeMod m2) = FreeMod (Map.mergeWithKey f id id m1 m2) where
f _ x y = case x+y of { 0 -> Nothing ; z -> Just z }
sub :: (Ord b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> FreeMod c b
sub (FreeMod m1) (FreeMod m2) = FreeMod (Map.mergeWithKey f id (Map.map negate) m1 m2) where
f _ x y = case x-y of { 0 -> Nothing ; z -> Just z }
scale :: (Ord b, Eq c, Num c) => c -> FreeMod c b -> FreeMod c b
scale 0 _ = zero
scale x (FreeMod m) = FreeMod (Map.mapMaybe f m) where
f y = case x*y of { 0 -> Nothing ; z -> Just z }
divideByConst :: (Ord b, Eq c, Integral c, Show c) => c -> FreeMod c b -> FreeMod c b
divideByConst d (FreeMod m) = FreeMod (Map.mapMaybe f m) where
f a = case divMod a d of
(b,0) -> case b of { 0 -> Nothing ; z -> Just z }
_ -> error $ "FreeMod/divideByConst: not divisible by " ++ show d
addScale :: (Ord b, Eq c, Num c) => FreeMod c b -> c -> FreeMod c b -> FreeMod c b
addScale (FreeMod m1) cf (FreeMod m2) =
if cf == 0
then FreeMod m1
else FreeMod (Map.mergeWithKey f id (Map.mapMaybe g) m1 m2)
where
g y = case cf*y of { 0 -> Nothing ; z -> Just z }
f _ x y = case x + cf*y of { 0 -> Nothing ; z -> Just z }
subScale :: (Ord b, Eq c, Num c) => FreeMod c b -> c -> FreeMod c b -> FreeMod c b
subScale (FreeMod m1) cf (FreeMod m2) =
if cf == 0
then FreeMod m1
else FreeMod (Map.mergeWithKey f id (Map.mapMaybe g) m1 m2)
where
g y = case - cf*y of { 0 -> Nothing ; z -> Just z }
f _ x y = case x - cf*y of { 0 -> Nothing ; z -> Just z }
sum :: (Ord b, Eq c, Num c) => [FreeMod c b] -> FreeMod c b
sum [] = zero
sum zms = (foldl1' add) zms
linComb :: (Ord b, Eq c, Num c) => [(c, FreeMod c b)] -> FreeMod c b
linComb = sumWith where
sumWith :: (Ord b, Eq c, Num c) => [(c, FreeMod c b)] -> FreeMod c b
sumWith [] = zero
sumWith zms = sum [ scale c zm | (c,zm) <- zms ]
flatMap :: (Ord b1, Ord b2, Eq c, Num c) => (b1 -> FreeMod c b2) -> FreeMod c b1 -> FreeMod c b2
flatMap f = sum . map g . Map.assocs . unFreeMod where
g (x,c) = scale c (f x)
flatMap' :: (Ord b1, Ord b2, Eq c2, Num c2) => (c1 -> c2) -> (b1 -> FreeMod c2 b2) -> FreeMod c1 b1 -> FreeMod c2 b2
flatMap' embed f = sum . map g . Map.assocs . unFreeMod where
g (x,c) = scale (embed c) (f x)
{-# SPECIALIZE histogram :: Ord b => [b] -> ZMod b #-}
histogram :: (Ord b, Num c) => [b] -> FreeMod c b
histogram xs = FreeMod $ foldl' f Map.empty xs where
f old x = Map.insertWith (+) x 1 old
one :: (Monoid b, Num c) => FreeMod c b
one = FreeMod (Map.singleton mempty 1)
konst :: (Monoid b, Eq c, Num c) => c -> FreeMod c b
konst c = FreeMod $ if c/=0
then Map.singleton mempty c
else Map.empty
mul :: (Ord b, Monoid b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> FreeMod c b
mul = mulWith (<>)
mul' :: (Ord b, PartialMonoid b, Eq c, Num c) => FreeMod c b -> FreeMod c b -> FreeMod c b
mul' = mulWith' (pmAdd)
product :: (Ord b, Monoid b, Eq c, Num c) => [FreeMod c b] -> FreeMod c b
product [] = generator mempty
product xs = foldl1' mul xs
product' :: (Ord b, PartialMonoid b, Eq c, Num c) => [FreeMod c b] -> FreeMod c b
product' [] = generator pmUnit
product' xs = foldl1' mul' xs
mulWith :: (Ord b, Eq c, Num c) => (b -> b -> b) -> FreeMod c b -> FreeMod c b -> FreeMod c b
mulWith op xx yy = normalize $ sum [ (f x c) | (x,c) <- toList xx ] where
f !x !c = FreeMod $ Map.fromListWith (+) [ (op x y, cd) | (y,d) <- ylist , let cd = c*d , cd /= 0 ]
ylist = toList yy
mulWith' :: (Ord b, Eq c, Num c) => (b -> b -> Maybe b) -> FreeMod c b -> FreeMod c b -> FreeMod c b
mulWith' op xx yy = normalize $ sum [ (f x c) | (x,c) <- toList xx ] where
f !x !c = FreeMod $ Map.fromListWith (+) [ (z, cd) | (y,d) <- ylist , Just z <- [op x y] , let cd = c*d , cd /= 0 ]
ylist = toList yy
mulWith'' :: (Ord b, Eq c, Num c) => (b -> b -> Maybe (b,c)) -> FreeMod c b -> FreeMod c b -> FreeMod c b
mulWith'' op xx yy = normalize $ sum [ (f x c) | (x,c) <- toList xx ] where
f !x !c = FreeMod $ Map.fromListWith (+) [ (z, cde) | (y,d) <- ylist , Just (z,e) <- [op x y] , let cde = c*d*e , cde /= 0 ]
ylist = toList yy
productWith :: (Ord b, Eq c, Num c) => b -> (b -> b -> b) -> [FreeMod c b] -> FreeMod c b
productWith empty op [] = generator empty
productWith empty op xs = foldl1' (mulWith op) xs
productWith' :: (Ord b, Eq c, Num c) => b -> (b -> b -> Maybe b) -> [FreeMod c b] -> FreeMod c b
productWith' empty op [] = generator empty
productWith' empty op xs = foldl1' (mulWith' op) xs
productWith'' :: (Ord b, Eq c, Num c) => b -> (b -> b -> Maybe (b,c)) -> [FreeMod c b] -> FreeMod c b
productWith'' empty op [] = generator empty
productWith'' empty op xs = foldl1' (mulWith'' op) xs
mulByMonom :: (Eq c, Num c, Ord b, Monoid b) => b -> FreeMod c b -> FreeMod c b
mulByMonom monom = mapBase (mappend monom)
unsafeMulByMonom :: (Ord b, Monoid b) => b -> FreeMod c b -> FreeMod c b
unsafeMulByMonom monom = unsafeMapBase (mappend monom)
mulByMonom' :: (Eq c, Num c, Ord b, PartialMonoid b) => b -> FreeMod c b -> FreeMod c b
mulByMonom' monom = mapMaybeBase (pmAdd monom)
unsafeMulByMonom' :: (Ord b, PartialMonoid b) => b -> FreeMod c b -> FreeMod c b
unsafeMulByMonom' monom = unsafeMapMaybeBase (pmAdd monom)
freeModCoeffProxy :: FreeMod c b -> Proxy c
freeModCoeffProxy _ = Proxy
fromZMod :: (Num c, Typeable c, Eq c, Num c, Ord b, Typeable b) => ZMod b -> FreeMod c b
fromZMod = unsafeCoeffChange fromInteger
fromQMod :: (Fractional c, Typeable c, Eq c, Num c, Ord b, Typeable b) => QMod b -> FreeMod c b
fromQMod = unsafeCoeffChange fromRational
unsafeCoeffChange :: (Typeable c1, Typeable c2, Eq c2, Num c2, Ord b, Typeable b) => (c1 -> c2) -> FreeMod c1 b -> FreeMod c2 b
unsafeCoeffChange f input = case cast input of
Just out -> out
Nothing -> mapCoeff f input
unsafeZModFromQMod :: Ord b => QMod b -> ZMod b
unsafeZModFromQMod = mapCoeff f where
f :: Rational -> Integer
f q = if denominator q == 1 then numerator q else error "unsafeZModFromQMod: coefficient is not integral"
mapBase :: (Ord a, Ord b, Eq c, Num c) => (a -> b) -> FreeMod c a -> FreeMod c b
mapBase f
= normalize
. onFreeMod (Map.mapKeysWith (+) f)
unsafeMapBase :: (Ord a, Ord b) => (a -> b) -> FreeMod c a -> FreeMod c b
unsafeMapBase f = onFreeMod (Map.mapKeys f)
mapCoeff :: (Ord b, Eq c2, Num c2) => (c1 -> c2) -> FreeMod c1 b -> FreeMod c2 b
mapCoeff f = onFreeMod' (Map.mapMaybe mbf) where
mbf x = case f x of { 0 -> Nothing ; y -> Just y }
mapCoeffWithKey :: (Ord b, Eq c2, Num c2) => (b -> c1 -> c2) -> FreeMod c1 b -> FreeMod c2 b
mapCoeffWithKey f = onFreeMod' (Map.mapMaybeWithKey mbf) where
mbf k x = case f k x of { 0 -> Nothing ; y -> Just y }
filterBase :: (Ord b) => (b -> Bool) -> FreeMod c b -> FreeMod c b
filterBase f = onFreeMod (Map.filterWithKey g) where g k _ = f k
mapMaybeBase :: (Ord a, Ord b, Eq c, Num c) => (a -> Maybe b) -> FreeMod c a -> FreeMod c b
mapMaybeBase f
= normalize
. onFreeMod (Map.fromListWith (+) . mapMaybe g . Map.toList)
where
g (k,x) = case f k of { Just k' -> Just (k',x) ; Nothing -> Nothing }
unsafeMapMaybeBase :: (Ord a, Ord b) => (a -> Maybe b) -> FreeMod c a -> FreeMod c b
unsafeMapMaybeBase f = onFreeMod (Map.fromList . mapMaybe g . Map.toList)
where
g (k,x) = case f k of { Just k' -> Just (k',x) ; Nothing -> Nothing }
mapMaybeBaseCoeff :: (Ord a, Ord b, Eq c, Num c) => (a -> Maybe (b,c)) -> FreeMod c a -> FreeMod c b
mapMaybeBaseCoeff f
= normalize
. onFreeMod (Map.fromListWith (+) . mapMaybe g . Map.toList)
where
g (k,x) = case f k of
Just (k',y) -> let z = x*y in if z/=0 then Just (k',z) else Nothing
Nothing -> Nothing
onFreeMod :: (Ord a, Ord b) => (Map a c -> Map b c) -> FreeMod c a -> FreeMod c b
onFreeMod f = FreeMod . f . unFreeMod
onFreeMod' :: (Ord a, Ord b) => (Map a c -> Map b d) -> FreeMod c a -> FreeMod d b
onFreeMod' f = FreeMod . f . unFreeMod