module Math.Algebras.NonCommutative where
import Prelude hiding ( (*>) )
import Math.Algebra.Field.Base hiding (powers)
import Math.Algebras.VectorSpace
import Math.Algebras.TensorProduct
import Math.Algebras.Structures
import qualified Data.List as L
data NonComMonomial v = NCM Int [v] deriving (Eq)
instance Ord v => Ord (NonComMonomial v) where
compare (NCM lx xs) (NCM ly ys) = compare (lx, xs) (ly, ys)
instance (Eq v, Show v) => Show (NonComMonomial v) where
show (NCM _ []) = "1"
show (NCM _ vs) = concatMap showPower (L.group vs)
where showPower [v] = showVar v
showPower vs@(v:_) = showVar v ++ "^" ++ show (length vs)
showVar v = filter (/= '"') (show v)
instance Mon (NonComMonomial v) where
munit = NCM 0 []
mmult (NCM i xs) (NCM j ys) = NCM (i+j) (xs++ys)
instance (Eq k, Num k, Ord v) => Algebra k (NonComMonomial v) where
unit 0 = zerov
unit x = V [(munit,x)]
mult = nf . fmap (\(a,b) -> a `mmult` b)
class Monomial m where
var :: v -> Vect Q (m v)
powers :: Eq v => m v -> [(v,Int)]
V ts `bind` f = sum [c *> product [f x ^ i | (x,i) <- powers m] | (m, c) <- ts]
instance Monomial NonComMonomial where
var v = V [(NCM 1 [v],1)]
powers (NCM _ vs) = map power (L.group vs)
where power vs@(v:_) = (v,length vs)
type NCPoly v = Vect Q (NonComMonomial v)
class DivisionBasis m where
divM :: m -> m -> Maybe (m,m)
instance Eq v => DivisionBasis (NonComMonomial v) where
divM (NCM _ a) (NCM _ b) = divM' [] a where
divM' ls (r:rs) =
if b `L.isPrefixOf` (r:rs)
then Just (ncm $ reverse ls, ncm $ drop (length b) (r:rs))
else divM' (r:ls) rs
divM' _ [] = Nothing
ncm xs = NCM (length xs) xs
lm (V ((m,c):ts)) = m
lc (V ((m,c):ts)) = c
lt (V (t:ts)) = V [t]
quotRemNP f gs | all (/=0) gs = quotRemNP' f (replicate n (0,0), 0)
| otherwise = error "quotRemNP: division by zero"
where
n = length gs
quotRemNP' 0 (lrs,f') = (lrs,f')
quotRemNP' h (lrs,f') = divisionStep h (gs,[],lrs,f')
divisionStep h (g:gs, lrs', (l,r):lrs, f') =
case lm h `divM` lm g of
Just (l',r') -> let l'' = V [(l',lc h / lc g)]
r'' = V [(r',1)]
h' = h l'' * g * r''
in quotRemNP' h' (reverse lrs' ++ (l+l'',r+r''):lrs, f')
Nothing -> divisionStep h (gs,(l,r):lrs',lrs,f')
divisionStep h ([],lrs',[],f') =
let lth = lt h
in quotRemNP' (hlth) (reverse lrs', f'+lth)
remNP f gs | all (/=0) gs = remNP' f 0
| otherwise = error "remNP: division by zero"
where
n = length gs
remNP' 0 f' = f'
remNP' h f' = divisionStep h gs f'
divisionStep h (g:gs) f' =
case lm h `divM` lm g of
Just (l',r') -> let l'' = V [(l',lc h / lc g)]
r'' = V [(r',1)]
h' = h l'' * g * r''
in remNP' h' f'
Nothing -> divisionStep h gs f'
divisionStep h [] f' =
let lth = lt h
in remNP' (hlth) (f'+lth)
infixl 7 %%
f %% gs = remNP f gs