{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Polynomial.Monomial
(
Mon(..),
Lex(..),
Revlex(..),
m,
mp,
)
where
import Data.Massiv.Array as A
import Prelude as P
import Data.Char.SScript
import Numeric.Algebra as N
import Data.Function
import Control.DeepSeq
import GHC.Generics (Generic, Generic1)
newtype Mon ord = Mon (Array P Ix1 Int) deriving (Generic, NFData, Eq)
data Lex = Lex
data Revlex = Revlex
m :: [Int] -> Mon ord
m [] = Mon $ A.fromList (ParN 1) []
m [0] = Mon $ A.fromList (ParN 1) []
m xs = Mon $ A.fromList (ParN 1) xs
mp :: [Int] -> [Int] -> Mon ord
mp xs xz
| lxs /= lxz = error "The size of the position and exponent doesn't correspond"
| otherwise = m $ mpRev xs xz 1
where
lxs = length xs
lxz = length xz
mpRev :: [Int] -> [Int] -> Int -> [Int]
mpRev [] [] _ = []
mpRev (p:ps) (x:xs) n
| p == 0 = error "The initial monomial position is 1 not 0"
| n /= p = 0 : mpRev (p : ps) (x : xs) next
| otherwise = x : mpRev ps xs next
where
next = n P.+ 1
instance Show (Mon ord) where
show (Mon m) = formatSS $ showMon (A.toList m) 1
showMon :: (Num a, Eq a, Ord a, Show a) => [a] -> Int -> String
showMon [] _ = ""
showMon (x:xs) s
| x == 0 = printMon
| null xs = format
| otherwise = format ++ printMon
where
next = succ
format = "x_{" ++ show s ++ "}^{" ++ show x ++ "}"
printMon = showMon xs (next s)
instance Multiplicative (Mon ord) where
(*) (Mon n) (Mon n') = m (quitZero $ on aux toList n n')
aux :: [Int] -> [Int] -> [Int]
aux [] [] = []
aux (x:xs) [] = x : aux xs []
aux [] (y:yp) = y : aux [] yp
aux (x:xs) (y:yp) = x P.+ y : aux xs yp
quitZero :: [Int] -> [Int]
quitZero [] = []
quitZero xs
| last xs == 0 = quitZero $ init xs
| otherwise = xs
instance Division (Mon ord) where
(/) (Mon n) (Mon n') = m (quitZero $ on aux' (A.toList) n n')
aux' :: [Int] -> [Int] -> [Int]
aux' [] [] = []
aux' (x:xs) [] = x : aux' xs []
aux' [] (y:yp) = y : aux' [] yp
aux' (x:xs) (y:yp) = x P.- y : aux' xs yp
instance Additive (Mon ord) where
(+) (Mon m)(Mon m') = Mon $ verificationMl m m'
instance Semiring (Mon ord)
instance Abelian (Mon ord)
instance Monoidal (Mon ord) where
zero = Mon empty
instance LeftModule Integer (Mon ord) where
(.*) = undefined
instance RightModule Integer (Mon ord) where
(*.) = undefined
instance LeftModule Natural (Mon ord) where
(.*) = undefined
instance RightModule Natural (Mon ord) where
(*.) = undefined
instance Group (Mon ord) where
(-) (Mon m)(Mon m') = Mon $ verificationMl m m'
verificationMl :: Array P Ix1 Int -> Array P Ix1 Int -> Array P Ix1 Int
verificationMl xs xz
| xs == xz = xs
| otherwise = error "The monomial doesn't match "
instance Ord (Mon Lex) where
compare (Mon m)(Mon m') = on lex' A.toList m m'
(>) (Mon m)(Mon m')= on (P.>) A.toList m m'
(<) (Mon m)(Mon m')= on (P.<) A.toList m m'
lex' :: (Num a, Eq a, Ord a) => [a] -> [a] -> Ordering
lex' [] [] = EQ
lex' [] _ = LT
lex' _ [] = GT
lex' (x:xs) (y:ys)
| x == y = lex' xs ys
| x P.> y = GT
| otherwise = LT
instance Ord (Mon Revlex) where
compare (Mon m)(Mon m')= on revlex' A.toList m m'
revlex' :: (Num a, Eq a, Ord a) => [a] -> [a] -> Ordering
revlex' = on lex' P.reverse
instance Unital (Mon ord ) where
one = undefined