{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Algebra.Ring.Polynomial.Quotient
( Quotient (),
QIdeal (),
reifyQuotient,
modIdeal,
modIdeal',
quotRepr,
withQuotient,
vectorRep,
genQuotVars,
genQuotVars',
gBasis',
matRep0,
standardMonomials,
standardMonomials',
matRepr',
reduce,
multWithTable,
multUnamb,
isZeroDimensional,
)
where
import Algebra.Algorithms.Groebner (calcGroebnerBasis)
import Algebra.Internal
import Algebra.Prelude.Core
import Algebra.Ring.Polynomial.Univariate (Unipol)
import Control.DeepSeq
import Control.Lens (folded, ifoldMap, minimumOf)
import qualified Data.Coerce as C
import qualified Data.HashMap.Lazy as HM
import Data.Kind (Type)
import qualified Data.Map as Map
import qualified Data.Matrix as M
import Data.MonoTraversable (osum)
import Data.Monoid (Sum (..))
import Data.Reflection
import Data.Unamb (unamb)
import qualified Data.Vector as V
import qualified Numeric.Algebra as NA
import qualified Prelude as P
newtype Quotient poly ideal = Quotient {Quotient poly ideal -> poly
quotRepr_ :: poly}
deriving (Quotient poly ideal -> Quotient poly ideal -> Bool
(Quotient poly ideal -> Quotient poly ideal -> Bool)
-> (Quotient poly ideal -> Quotient poly ideal -> Bool)
-> Eq (Quotient poly ideal)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall poly k (ideal :: k).
Eq poly =>
Quotient poly ideal -> Quotient poly ideal -> Bool
/= :: Quotient poly ideal -> Quotient poly ideal -> Bool
$c/= :: forall poly k (ideal :: k).
Eq poly =>
Quotient poly ideal -> Quotient poly ideal -> Bool
== :: Quotient poly ideal -> Quotient poly ideal -> Bool
$c== :: forall poly k (ideal :: k).
Eq poly =>
Quotient poly ideal -> Quotient poly ideal -> Bool
Eq)
quotRepr :: Quotient poly ideal -> poly
quotRepr :: Quotient poly ideal -> poly
quotRepr = Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_
data QIdeal poly
= ZeroDimIdeal
{ QIdeal poly -> [poly]
_gBasis :: ![poly]
, QIdeal poly -> [OrderedMonomial (MOrder poly) (Arity poly)]
_vBasis :: ![OrderedMonomial (MOrder poly) (Arity poly)]
, QIdeal poly -> Table poly
multTable :: Table poly
}
| QIdeal
{ _gBasis :: [poly]
}
instance NFData poly => NFData (Quotient poly ideal) where
rnf :: Quotient poly ideal -> ()
rnf (Quotient poly
op) = poly -> ()
forall a. NFData a => a -> ()
rnf poly
op
type Table poly =
HM.HashMap
( OrderedMonomial (MOrder poly) (Arity poly)
, OrderedMonomial (MOrder poly) (Arity poly)
)
poly
vectorRep ::
forall poly ideal.
(IsOrderedPolynomial poly, Reifies ideal (QIdeal poly)) =>
Quotient poly ideal ->
V.Vector (Coefficient poly)
vectorRep :: Quotient poly ideal -> Vector (Coefficient poly)
vectorRep Quotient poly ideal
f =
let ZeroDimIdeal [poly]
_ [OrderedMonomial (MOrder poly) (Arity poly)]
base Table poly
_ = Quotient poly ideal -> QIdeal poly
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect Quotient poly ideal
f
mf :: poly
mf = Quotient poly ideal -> poly
forall k poly (ideal :: k). Quotient poly ideal -> poly
quotRepr Quotient poly ideal
f
in [Coefficient poly] -> Vector (Coefficient poly)
forall a. [a] -> Vector a
V.fromList ([Coefficient poly] -> Vector (Coefficient poly))
-> [Coefficient poly] -> Vector (Coefficient poly)
forall a b. (a -> b) -> a -> b
$ (OrderedMonomial (MOrder poly) (Arity poly) -> Coefficient poly)
-> [OrderedMonomial (MOrder poly) (Arity poly)]
-> [Coefficient poly]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map ((OrderedMonomial (MOrder poly) (Arity poly)
-> poly -> Coefficient poly)
-> poly
-> OrderedMonomial (MOrder poly) (Arity poly)
-> Coefficient poly
forall a b c. (a -> b -> c) -> b -> a -> c
flip OrderedMonomial (MOrder poly) (Arity poly)
-> poly -> Coefficient poly
forall poly.
IsOrderedPolynomial poly =>
OrderedMonomial (MOrder poly) (Arity poly)
-> poly -> Coefficient poly
coeff poly
mf) [OrderedMonomial (MOrder poly) (Arity poly)]
base
{-# SPECIALIZE INLINE vectorRep ::
( IsMonomialOrder n ord
, CoeffRing r
, KnownNat n
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Quotient (OrderedPolynomial r ord n) ideal ->
V.Vector r
#-}
{-# SPECIALIZE INLINE vectorRep ::
(CoeffRing r, Reifies ideal (QIdeal (Unipol r))) =>
Quotient (Unipol r) ideal ->
V.Vector r
#-}
{-# SPECIALIZE INLINE vectorRep ::
( IsMonomialOrder n ord
, KnownNat n
, Reifies ideal (QIdeal (OrderedPolynomial Rational ord n))
) =>
Quotient (OrderedPolynomial Rational ord n) ideal ->
V.Vector Rational
#-}
{-# SPECIALIZE INLINE vectorRep ::
(Reifies ideal (QIdeal (Unipol Rational))) =>
Quotient (Unipol Rational) ideal ->
V.Vector Rational
#-}
{-# INLINE vectorRep #-}
matRepr' ::
forall poly ideal.
( Field (Coefficient poly)
, Reifies ideal (QIdeal poly)
, IsOrderedPolynomial poly
) =>
Quotient poly ideal ->
M.Matrix (Coefficient poly)
matRepr' :: Quotient poly ideal -> Matrix (Coefficient poly)
matRepr' Quotient poly ideal
f =
let ZeroDimIdeal [poly]
_bs [OrderedMonomial (MOrder poly) (Arity poly)]
_ Table poly
_ = Quotient poly ideal -> QIdeal poly
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect Quotient poly ideal
f
in Matrix (WrapAlgebra (Coefficient poly))
-> Matrix (Coefficient poly)
C.coerce (Matrix (WrapAlgebra (Coefficient poly))
-> Matrix (Coefficient poly))
-> Matrix (WrapAlgebra (Coefficient poly))
-> Matrix (Coefficient poly)
forall a b. (a -> b) -> a -> b
$
Sum (Matrix (WrapAlgebra (Coefficient poly)))
-> Matrix (WrapAlgebra (Coefficient poly))
forall a. Sum a -> a
getSum (Sum (Matrix (WrapAlgebra (Coefficient poly)))
-> Matrix (WrapAlgebra (Coefficient poly)))
-> Sum (Matrix (WrapAlgebra (Coefficient poly)))
-> Matrix (WrapAlgebra (Coefficient poly))
forall a b. (a -> b) -> a -> b
$
(OrderedMonomial (MOrder poly) (Arity poly)
-> Coefficient poly
-> Sum (Matrix (WrapAlgebra (Coefficient poly))))
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
-> Sum (Matrix (WrapAlgebra (Coefficient poly)))
forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap
( \OrderedMonomial (MOrder poly) (Arity poly)
t Coefficient poly
c ->
Matrix (WrapAlgebra (Coefficient poly))
-> Sum (Matrix (WrapAlgebra (Coefficient poly)))
forall a. a -> Sum a
Sum (Matrix (WrapAlgebra (Coefficient poly))
-> Sum (Matrix (WrapAlgebra (Coefficient poly))))
-> Matrix (WrapAlgebra (Coefficient poly))
-> Sum (Matrix (WrapAlgebra (Coefficient poly)))
forall a b. (a -> b) -> a -> b
$ (Coefficient poly -> WrapAlgebra (Coefficient poly))
-> Matrix (Coefficient poly)
-> Matrix (WrapAlgebra (Coefficient poly))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Coefficient poly -> WrapAlgebra (Coefficient poly)
forall a. a -> WrapAlgebra a
WrapAlgebra (Coefficient poly -> WrapAlgebra (Coefficient poly))
-> (Coefficient poly -> Coefficient poly)
-> Coefficient poly
-> WrapAlgebra (Coefficient poly)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coefficient poly
c Coefficient poly -> Coefficient poly -> Coefficient poly
forall r. Multiplicative r => r -> r -> r
*)) (Matrix (Coefficient poly)
-> Matrix (WrapAlgebra (Coefficient poly)))
-> Matrix (Coefficient poly)
-> Matrix (WrapAlgebra (Coefficient poly))
forall a b. (a -> b) -> a -> b
$ Proxy poly
-> Proxy ideal
-> OrderedMonomial (MOrder poly) (Arity poly)
-> Matrix (Coefficient poly)
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
Proxy poly
-> Proxy ideal
-> OrderedMonomial (MOrder poly) (Arity poly)
-> Matrix (Coefficient poly)
matRep0 (Proxy poly
forall k (t :: k). Proxy t
Proxy :: Proxy poly) (Proxy ideal
forall k (t :: k). Proxy t
Proxy :: Proxy ideal) OrderedMonomial (MOrder poly) (Arity poly)
t
)
(poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
forall poly.
IsOrderedPolynomial poly =>
poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
terms (Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f))
{-# SPECIALIZE INLINE matRepr' ::
( IsMonomialOrder n ord
, CoeffRing r
, KnownNat n
, Field r
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Quotient (OrderedPolynomial r ord n) ideal ->
M.Matrix r
#-}
{-# SPECIALIZE INLINE matRepr' ::
(Field r, CoeffRing r, Reifies ideal (QIdeal (Unipol r))) =>
Quotient (Unipol r) ideal ->
M.Matrix r
#-}
{-# SPECIALIZE INLINE matRepr' ::
( IsMonomialOrder n ord
, KnownNat n
, Reifies ideal (QIdeal (OrderedPolynomial Rational ord n))
) =>
Quotient (OrderedPolynomial Rational ord n) ideal ->
M.Matrix Rational
#-}
{-# SPECIALIZE INLINE matRepr' ::
(Reifies ideal (QIdeal (Unipol Rational))) =>
Quotient (Unipol Rational) ideal ->
M.Matrix Rational
#-}
{-# INLINE matRepr' #-}
matRep0 ::
forall poly ideal.
(IsOrderedPolynomial poly, Field (Coefficient poly), Reifies ideal (QIdeal poly)) =>
Proxy poly ->
Proxy ideal ->
OrderedMonomial (MOrder poly) (Arity poly) ->
M.Matrix (Coefficient poly)
matRep0 :: Proxy poly
-> Proxy ideal
-> OrderedMonomial (MOrder poly) (Arity poly)
-> Matrix (Coefficient poly)
matRep0 Proxy poly
_ Proxy ideal
pxy OrderedMonomial (MOrder poly) (Arity poly)
m =
let ZeroDimIdeal [poly]
_ [OrderedMonomial (MOrder poly) (Arity poly)]
bs Table poly
table = Proxy ideal -> QIdeal poly
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect Proxy ideal
pxy
in (Matrix (Coefficient poly)
-> Matrix (Coefficient poly) -> Matrix (Coefficient poly))
-> Matrix (Coefficient poly)
-> [Matrix (Coefficient poly)]
-> Matrix (Coefficient poly)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr
Matrix (Coefficient poly)
-> Matrix (Coefficient poly) -> Matrix (Coefficient poly)
forall a. Matrix a -> Matrix a -> Matrix a
(M.<|>)
(Int -> Int -> [Coefficient poly] -> Matrix (Coefficient poly)
forall a. Int -> Int -> [a] -> Matrix a
M.fromList Int
0 Int
0 [])
[ Vector (Coefficient poly) -> Matrix (Coefficient poly)
forall a. Vector a -> Matrix a
M.colVector (Vector (Coefficient poly) -> Matrix (Coefficient poly))
-> Vector (Coefficient poly) -> Matrix (Coefficient poly)
forall a b. (a -> b) -> a -> b
$ Quotient poly ideal -> Vector (Coefficient poly)
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Reifies ideal (QIdeal poly)) =>
Quotient poly ideal -> Vector (Coefficient poly)
vectorRep (Quotient poly ideal -> Vector (Coefficient poly))
-> Quotient poly ideal -> Vector (Coefficient poly)
forall a b. (a -> b) -> a -> b
$ Proxy ideal -> poly -> Quotient poly ideal
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
Proxy ideal -> poly -> Quotient poly ideal
modIdeal' Proxy ideal
pxy (poly
-> (OrderedMonomial (MOrder poly) (Arity poly),
OrderedMonomial (MOrder poly) (Arity poly))
-> Table poly
-> poly
forall k v. (Eq k, Hashable k) => v -> k -> HashMap k v -> v
HM.lookupDefault poly
forall m. Monoidal m => m
zero (OrderedMonomial (MOrder poly) (Arity poly)
m, OrderedMonomial (MOrder poly) (Arity poly)
b) Table poly
table)
| OrderedMonomial (MOrder poly) (Arity poly)
b <- [OrderedMonomial (MOrder poly) (Arity poly)]
bs
]
{-# SPECIALIZE INLINE matRep0 ::
( IsMonomialOrder n ord
, Field r
, CoeffRing r
, KnownNat n
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Proxy (OrderedPolynomial r ord n) ->
Proxy ideal ->
OrderedMonomial ord n ->
M.Matrix r
#-}
{-# SPECIALIZE INLINE matRep0 ::
(CoeffRing r, Field r, Reifies ideal (QIdeal (Unipol r))) =>
Proxy (Unipol r) ->
Proxy ideal ->
OrderedMonomial Grevlex 1 ->
M.Matrix r
#-}
{-# SPECIALIZE INLINE matRep0 ::
( IsMonomialOrder n ord
, KnownNat n
, Reifies ideal (QIdeal (OrderedPolynomial Rational ord n))
) =>
Proxy (OrderedPolynomial Rational ord n) ->
Proxy ideal ->
OrderedMonomial ord n ->
M.Matrix Rational
#-}
{-# SPECIALIZE INLINE matRep0 ::
(Reifies ideal (QIdeal (Unipol Rational))) =>
Proxy (Unipol Rational) ->
Proxy ideal ->
OrderedMonomial Grevlex 1 ->
M.Matrix Rational
#-}
{-# INLINE matRep0 #-}
multUnamb ::
( IsOrderedPolynomial poly
, Field (Coefficient poly)
, Reifies ideal (QIdeal poly)
) =>
Quotient poly ideal ->
Quotient poly ideal ->
Quotient poly ideal
multUnamb :: Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
multUnamb Quotient poly ideal
a Quotient poly ideal
b = Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
forall a. a -> a -> a
unamb (Quotient poly ideal
a Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
forall r. Multiplicative r => r -> r -> r
* Quotient poly ideal
b) (Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Reifies ideal (QIdeal poly)) =>
Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
multWithTable Quotient poly ideal
a Quotient poly ideal
b)
{-# SPECIALIZE INLINE multUnamb ::
( CoeffRing r
, IsMonomialOrder n ord
, KnownNat n
, Field r
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Quotient (OrderedPolynomial r ord n) ideal ->
Quotient (OrderedPolynomial r ord n) ideal ->
Quotient (OrderedPolynomial r ord n) ideal
#-}
{-# SPECIALIZE INLINE multUnamb ::
(CoeffRing r, Field r, Reifies ideal (QIdeal (Unipol r))) =>
Quotient (Unipol r) ideal ->
Quotient (Unipol r) ideal ->
Quotient (Unipol r) ideal
#-}
{-# SPECIALIZE INLINE multUnamb ::
( IsMonomialOrder n ord
, KnownNat n
, Reifies ideal (QIdeal (OrderedPolynomial Rational ord n))
) =>
Quotient (OrderedPolynomial Rational ord n) ideal ->
Quotient (OrderedPolynomial Rational ord n) ideal ->
Quotient (OrderedPolynomial Rational ord n) ideal
#-}
{-# SPECIALIZE INLINE multUnamb ::
(Reifies ideal (QIdeal (Unipol Rational))) =>
Quotient (Unipol Rational) ideal ->
Quotient (Unipol Rational) ideal ->
Quotient (Unipol Rational) ideal
#-}
{-# INLINE multUnamb #-}
multWithTable ::
(IsOrderedPolynomial poly, Reifies ideal (QIdeal poly)) =>
Quotient poly ideal ->
Quotient poly ideal ->
Quotient poly ideal
multWithTable :: Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
multWithTable Quotient poly ideal
f Quotient poly ideal
g =
let qid :: QIdeal poly
qid = Quotient poly ideal -> QIdeal poly
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect Quotient poly ideal
f
table :: Table poly
table = QIdeal poly -> Table poly
forall poly. QIdeal poly -> Table poly
multTable QIdeal poly
qid
in [Quotient poly ideal] -> Quotient poly ideal
forall (f :: * -> *) m. (Foldable f, Monoidal m) => f m -> m
sum
[ poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ Coefficient poly
c Coefficient poly -> poly -> poly
forall r m. Module (Scalar r) m => r -> m -> m
.*. Coefficient poly
d Coefficient poly -> poly -> poly
forall r m. Module (Scalar r) m => r -> m -> m
.*. (poly
-> (OrderedMonomial (MOrder poly) (Arity poly),
OrderedMonomial (MOrder poly) (Arity poly))
-> Table poly
-> poly
forall k v. (Eq k, Hashable k) => v -> k -> HashMap k v -> v
HM.lookupDefault poly
forall m. Monoidal m => m
zero (OrderedMonomial (MOrder poly) (Arity poly)
l, OrderedMonomial (MOrder poly) (Arity poly)
r) Table poly
table)
| (OrderedMonomial (MOrder poly) (Arity poly)
l, Coefficient poly
c) <- Map (OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
-> [(OrderedMonomial (MOrder poly) (Arity poly), Coefficient poly)]
forall k a. Map k a -> [(k, a)]
Map.toList (Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
-> [(OrderedMonomial (MOrder poly) (Arity poly),
Coefficient poly)])
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
-> [(OrderedMonomial (MOrder poly) (Arity poly), Coefficient poly)]
forall a b. (a -> b) -> a -> b
$ poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
forall poly.
IsOrderedPolynomial poly =>
poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
terms (poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly))
-> poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
forall a b. (a -> b) -> a -> b
$ Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f
, (OrderedMonomial (MOrder poly) (Arity poly)
r, Coefficient poly
d) <- Map (OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
-> [(OrderedMonomial (MOrder poly) (Arity poly), Coefficient poly)]
forall k a. Map k a -> [(k, a)]
Map.toList (Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
-> [(OrderedMonomial (MOrder poly) (Arity poly),
Coefficient poly)])
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
-> [(OrderedMonomial (MOrder poly) (Arity poly), Coefficient poly)]
forall a b. (a -> b) -> a -> b
$ poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
forall poly.
IsOrderedPolynomial poly =>
poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
terms (poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly))
-> poly
-> Map
(OrderedMonomial (MOrder poly) (Arity poly)) (Coefficient poly)
forall a b. (a -> b) -> a -> b
$ Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
g
]
{-# SPECIALIZE INLINE multWithTable ::
( CoeffRing r
, IsMonomialOrder n ord
, KnownNat n
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Quotient (OrderedPolynomial r ord n) ideal ->
Quotient (OrderedPolynomial r ord n) ideal ->
Quotient (OrderedPolynomial r ord n) ideal
#-}
{-# SPECIALIZE INLINE multWithTable ::
(CoeffRing r, Reifies ideal (QIdeal (Unipol r))) =>
Quotient (Unipol r) ideal ->
Quotient (Unipol r) ideal ->
Quotient (Unipol r) ideal
#-}
{-# INLINE multWithTable #-}
instance Show poly => Show (Quotient poly ideal) where
show :: Quotient poly ideal -> String
show (Quotient poly
f) = poly -> String
forall a. Show a => a -> String
show poly
f
buildMultTable ::
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
[poly] ->
[OrderedMonomial (MOrder poly) (Arity poly)] ->
Table poly
buildMultTable :: [poly]
-> [OrderedMonomial (MOrder poly) (Arity poly)] -> Table poly
buildMultTable [poly]
bs [OrderedMonomial (MOrder poly) (Arity poly)]
ms =
[((OrderedMonomial (MOrder poly) (Arity poly),
OrderedMonomial (MOrder poly) (Arity poly)),
poly)]
-> Table poly
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList
[ ((OrderedMonomial (MOrder poly) (Arity poly)
p, OrderedMonomial (MOrder poly) (Arity poly)
q), ((Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly
forall poly.
IsOrderedPolynomial poly =>
(Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly
toPolynomial (Coefficient poly
forall r. Unital r => r
one, OrderedMonomial (MOrder poly) (Arity poly)
p) poly -> poly -> poly
forall r. Multiplicative r => r -> r -> r
* (Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly
forall poly.
IsOrderedPolynomial poly =>
(Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly
toPolynomial (Coefficient poly
forall r. Unital r => r
one, OrderedMonomial (MOrder poly) (Arity poly)
q)) poly -> [poly] -> poly
forall poly (t :: * -> *).
(IsOrderedPolynomial poly, Field (Coefficient poly), Functor t,
Foldable t) =>
poly -> t poly -> poly
`modPolynomial` [poly]
bs)
| OrderedMonomial (MOrder poly) (Arity poly)
p <- [OrderedMonomial (MOrder poly) (Arity poly)]
ms
, OrderedMonomial (MOrder poly) (Arity poly)
q <- [OrderedMonomial (MOrder poly) (Arity poly)]
ms
]
{-# SPECIALIZE INLINE buildMultTable ::
(IsMonomialOrder n ord, Field r, CoeffRing r, KnownNat n) =>
[OrderedPolynomial r ord n] ->
[OrderedMonomial ord n] ->
Table (OrderedPolynomial r ord n)
#-}
{-# SPECIALIZE INLINE buildMultTable ::
(Field r, CoeffRing r) =>
[Unipol r] ->
[OrderedMonomial Grevlex 1] ->
Table (Unipol r)
#-}
stdMonoms ::
forall poly.
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
[poly] ->
Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
stdMonoms :: [poly] -> Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
stdMonoms [poly]
basis = do
let lms :: [(Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))]
lms = (poly
-> (Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly)))
-> [poly]
-> [(Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map poly
-> (Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
forall poly.
IsOrderedPolynomial poly =>
poly
-> (Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
leadingTerm [poly]
basis
dim :: SNat (Arity poly)
dim = SNat (Arity poly)
forall (n :: Nat). KnownNat n => SNat n
sNat :: SNat (Arity poly)
tests :: [(USized (Arity poly) Int, USized (Arity poly) Int)]
tests = [USized (Arity poly) Int]
-> [USized (Arity poly) Int]
-> [(USized (Arity poly) Int, USized (Arity poly) Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Int -> Int -> SNat (Arity poly) -> [USized (Arity poly) Int]
forall a (n :: Nat). Unbox a => a -> a -> SNat n -> [USized n a]
diag Int
1 Int
0 SNat (Arity poly)
dim) (Int -> Int -> SNat (Arity poly) -> [USized (Arity poly) Int]
forall a (n :: Nat). Unbox a => a -> a -> SNat n -> [USized n a]
diag Int
0 Int
1 SNat (Arity poly)
dim)
mexp :: (USized (Arity poly) Int, USized (Arity poly) Int) -> [Int]
mexp (USized (Arity poly) Int
val, USized (Arity poly) Int
test) =
[ USized (Arity poly) Int -> Element (USized (Arity poly) Int)
forall mono.
(MonoFoldable mono, Num (Element mono)) =>
mono -> Element mono
osum (USized (Arity poly) Int -> Element (USized (Arity poly) Int))
-> USized (Arity poly) Int -> Element (USized (Arity poly) Int)
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int)
-> USized (Arity poly) Int
-> USized (Arity poly) Int
-> USized (Arity poly) Int
forall (f :: * -> *) (n :: Nat) a b c.
(Dom f a, CZip f, Dom f b, CFreeMonoid f, Dom f c) =>
(a -> b -> c) -> Sized f n a -> Sized f n b -> Sized f n c
zipWithSame Int -> Int -> Int
forall r. Multiplicative r => r -> r -> r
(*) USized (Arity poly) Int
val (USized (Arity poly) Int -> USized (Arity poly) Int)
-> USized (Arity poly) Int -> USized (Arity poly) Int
forall a b. (a -> b) -> a -> b
$ OrderedMonomial (MOrder poly) (Arity poly)
-> USized (Arity poly) Int
forall k (ordering :: k) (n :: Nat).
OrderedMonomial ordering n -> Monomial n
getMonomial OrderedMonomial (MOrder poly) (Arity poly)
lm0
| (Coefficient poly
c, OrderedMonomial (MOrder poly) (Arity poly)
lm0) <- [(Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))]
lms
, Coefficient poly
c Coefficient poly -> Coefficient poly -> Bool
forall a. Eq a => a -> a -> Bool
/= Coefficient poly
forall m. Monoidal m => m
zero
, let a :: Element (USized (Arity poly) Int)
a = USized (Arity poly) Int -> Element (USized (Arity poly) Int)
forall mono.
(MonoFoldable mono, Num (Element mono)) =>
mono -> Element mono
osum (USized (Arity poly) Int -> Element (USized (Arity poly) Int))
-> USized (Arity poly) Int -> Element (USized (Arity poly) Int)
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int)
-> USized (Arity poly) Int
-> USized (Arity poly) Int
-> USized (Arity poly) Int
forall (f :: * -> *) (n :: Nat) a b c.
(Dom f a, CZip f, Dom f b, CFreeMonoid f, Dom f c) =>
(a -> b -> c) -> Sized f n a -> Sized f n b -> Sized f n c
zipWithSame Int -> Int -> Int
forall r. Multiplicative r => r -> r -> r
(*) (OrderedMonomial (MOrder poly) (Arity poly)
-> USized (Arity poly) Int
forall k (ordering :: k) (n :: Nat).
OrderedMonomial ordering n -> Monomial n
getMonomial OrderedMonomial (MOrder poly) (Arity poly)
lm0) USized (Arity poly) Int
test
, Int
Element (USized (Arity poly) Int)
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
]
[Int]
degs <- ((USized (Arity poly) Int, USized (Arity poly) Int) -> Maybe Int)
-> [(USized (Arity poly) Int, USized (Arity poly) Int)]
-> Maybe [Int]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Getting (Endo (Endo (Maybe Int))) [Int] Int -> [Int] -> Maybe Int
forall a s.
Ord a =>
Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a
minimumOf Getting (Endo (Endo (Maybe Int))) [Int] Int
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
folded ([Int] -> Maybe Int)
-> ((USized (Arity poly) Int, USized (Arity poly) Int) -> [Int])
-> (USized (Arity poly) Int, USized (Arity poly) Int)
-> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (USized (Arity poly) Int, USized (Arity poly) Int) -> [Int]
mexp) [(USized (Arity poly) Int, USized (Arity poly) Int)]
tests
[OrderedMonomial (MOrder poly) (Arity poly)]
-> Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
forall (m :: * -> *) a. Monad m => a -> m a
return ([OrderedMonomial (MOrder poly) (Arity poly)]
-> Maybe [OrderedMonomial (MOrder poly) (Arity poly)])
-> [OrderedMonomial (MOrder poly) (Arity poly)]
-> Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
forall a b. (a -> b) -> a -> b
$
[OrderedMonomial (MOrder poly) (Arity poly)]
-> [OrderedMonomial (MOrder poly) (Arity poly)]
forall a. Ord a => [a] -> [a]
sort
[ OrderedMonomial (MOrder poly) (Arity poly)
monom
| [Int]
ds0 <- (Int -> [Int]) -> [Int] -> [[Int]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Int -> Int -> [Int]
forall a. Enum a => a -> a -> [a]
enumFromTo Int
0) [Int]
degs
, let monom :: OrderedMonomial (MOrder poly) (Arity poly)
monom = USized (Arity poly) Int
-> OrderedMonomial (MOrder poly) (Arity poly)
forall k (ordering :: k) (n :: Nat).
Monomial n -> OrderedMonomial ordering n
OrderedMonomial (USized (Arity poly) Int
-> OrderedMonomial (MOrder poly) (Arity poly))
-> USized (Arity poly) Int
-> OrderedMonomial (MOrder poly) (Arity poly)
forall a b. (a -> b) -> a -> b
$ SNat (Arity poly) -> [Int] -> USized (Arity poly) Int
forall (n :: Nat). SNat n -> [Int] -> Monomial n
fromList SNat (Arity poly)
dim [Int]
ds0
, let ds :: poly
ds = (Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly
forall poly.
IsOrderedPolynomial poly =>
(Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly
toPolynomial (Coefficient poly
forall r. Unital r => r
one, OrderedMonomial (MOrder poly) (Arity poly)
monom)
, poly
ds poly -> [poly] -> poly
forall poly (t :: * -> *).
(IsOrderedPolynomial poly, Field (Coefficient poly), Functor t,
Foldable t) =>
poly -> t poly -> poly
`modPolynomial` [poly]
basis poly -> poly -> Bool
forall a. Eq a => a -> a -> Bool
== poly
ds
]
{-# SPECIALIZE stdMonoms ::
(IsMonomialOrder n ord, Field r, CoeffRing r, KnownNat n) =>
[OrderedPolynomial r ord n] ->
Maybe [OrderedMonomial ord n]
#-}
{-# SPECIALIZE stdMonoms ::
(Field r, CoeffRing r) =>
[Unipol r] ->
Maybe [OrderedMonomial Grevlex 1]
#-}
diag :: Unbox a => a -> a -> SNat n -> [USized n a]
diag :: a -> a -> SNat n -> [USized n a]
diag a
d a
z SNat n
n =
[ SNat n -> (Ordinal n -> a) -> USized n a
forall (f :: * -> *) (n :: Nat) a.
(CFreeMonoid f, Dom f a) =>
SNat n -> (Ordinal n -> a) -> Sized f n a
generate SNat n
n (\Ordinal n
j -> if Ordinal n
i Ordinal n -> Ordinal n -> Bool
forall a. Eq a => a -> a -> Bool
== Ordinal n
j then a
d else a
z)
| Ordinal n
i <- SNat n -> [Ordinal n]
forall (n :: Nat). SNat n -> [Ordinal n]
enumOrdinal SNat n
n
]
{-# INLINE diag #-}
standardMonomials' ::
( IsOrderedPolynomial poly
, Field (Coefficient poly)
, Reifies ideal (QIdeal poly)
) =>
Proxy ideal ->
Maybe [Quotient poly ideal]
standardMonomials' :: Proxy ideal -> Maybe [Quotient poly ideal]
standardMonomials' Proxy ideal
pxy =
case Proxy ideal -> QIdeal poly
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect Proxy ideal
pxy of
ZeroDimIdeal [poly]
_ [OrderedMonomial (MOrder poly) (Arity poly)]
vB Table poly
_ -> [Quotient poly ideal] -> Maybe [Quotient poly ideal]
forall a. a -> Maybe a
Just ([Quotient poly ideal] -> Maybe [Quotient poly ideal])
-> [Quotient poly ideal] -> Maybe [Quotient poly ideal]
forall a b. (a -> b) -> a -> b
$ (OrderedMonomial (MOrder poly) (Arity poly) -> Quotient poly ideal)
-> [OrderedMonomial (MOrder poly) (Arity poly)]
-> [Quotient poly ideal]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map (poly -> Quotient poly ideal
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
poly -> Quotient poly ideal
modIdeal (poly -> Quotient poly ideal)
-> (OrderedMonomial (MOrder poly) (Arity poly) -> poly)
-> OrderedMonomial (MOrder poly) (Arity poly)
-> Quotient poly ideal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly
forall poly.
IsOrderedPolynomial poly =>
(Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly
toPolynomial ((Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly))
-> poly)
-> (OrderedMonomial (MOrder poly) (Arity poly)
-> (Coefficient poly, OrderedMonomial (MOrder poly) (Arity poly)))
-> OrderedMonomial (MOrder poly) (Arity poly)
-> poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,) Coefficient poly
forall r. Unital r => r
one) [OrderedMonomial (MOrder poly) (Arity poly)]
vB
QIdeal poly
_ -> Maybe [Quotient poly ideal]
forall a. Maybe a
Nothing
{-# SPECIALIZE INLINE standardMonomials' ::
( IsMonomialOrder n ord
, CoeffRing r
, KnownNat n
, Field r
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Proxy ideal ->
Maybe [Quotient (OrderedPolynomial r ord n) ideal]
#-}
{-# SPECIALIZE INLINE standardMonomials' ::
(CoeffRing r, Field r, Reifies ideal (QIdeal (Unipol r))) =>
Proxy ideal ->
Maybe [Quotient (Unipol r) ideal]
#-}
{-# INLINE standardMonomials' #-}
standardMonomials ::
forall poly ideal.
( IsOrderedPolynomial poly
, Field (Coefficient poly)
, Reifies ideal (QIdeal poly)
) =>
Maybe [Quotient poly ideal]
standardMonomials :: Maybe [Quotient poly ideal]
standardMonomials = Proxy ideal -> Maybe [Quotient poly ideal]
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
Proxy ideal -> Maybe [Quotient poly ideal]
standardMonomials' (Proxy ideal
forall k (t :: k). Proxy t
Proxy :: Proxy ideal)
{-# SPECIALIZE INLINE standardMonomials ::
( IsMonomialOrder n ord
, CoeffRing r
, KnownNat n
, Field r
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Maybe [Quotient (OrderedPolynomial r ord n) ideal]
#-}
{-# SPECIALIZE INLINE standardMonomials ::
(CoeffRing r, Field r, Reifies ideal (QIdeal (Unipol r))) =>
Maybe [Quotient (Unipol r) ideal]
#-}
{-# INLINE standardMonomials #-}
genQuotVars' ::
forall poly ideal.
( IsOrderedPolynomial poly
, Field (Coefficient poly)
, Reifies ideal (QIdeal poly)
) =>
Proxy ideal ->
[Quotient poly ideal]
genQuotVars' :: Proxy ideal -> [Quotient poly ideal]
genQuotVars' Proxy ideal
pxy = (poly -> Quotient poly ideal) -> [poly] -> [Quotient poly ideal]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map (Proxy ideal -> poly -> Quotient poly ideal
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
Proxy ideal -> poly -> Quotient poly ideal
modIdeal' Proxy ideal
pxy) [poly]
forall poly. IsPolynomial poly => [poly]
vars
{-# SPECIALIZE INLINE genQuotVars' ::
( IsMonomialOrder n ord
, CoeffRing r
, KnownNat n
, Field r
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Proxy ideal ->
[Quotient (OrderedPolynomial r ord n) ideal]
#-}
{-# SPECIALIZE INLINE genQuotVars' ::
(CoeffRing r, Field r, Reifies ideal (QIdeal (Unipol r))) =>
Proxy ideal ->
[Quotient (Unipol r) ideal]
#-}
{-# INLINE genQuotVars' #-}
genQuotVars ::
forall poly ideal.
( IsOrderedPolynomial poly
, Field (Coefficient poly)
, Reifies ideal (QIdeal poly)
) =>
[Quotient poly ideal]
genQuotVars :: [Quotient poly ideal]
genQuotVars = Proxy ideal -> [Quotient poly ideal]
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
Proxy ideal -> [Quotient poly ideal]
genQuotVars' (Proxy ideal
forall k (t :: k). Proxy t
Proxy :: Proxy ideal)
{-# SPECIALIZE INLINE genQuotVars ::
( IsMonomialOrder n ord
, CoeffRing r
, KnownNat n
, Field r
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
[Quotient (OrderedPolynomial r ord n) ideal]
#-}
{-# SPECIALIZE INLINE genQuotVars ::
(CoeffRing r, Field r, Reifies ideal (QIdeal (Unipol r))) =>
[Quotient (Unipol r) ideal]
#-}
{-# INLINE genQuotVars #-}
modIdeal ::
forall poly ideal.
( IsOrderedPolynomial poly
, Field (Coefficient poly)
, Reifies ideal (QIdeal poly)
) =>
poly ->
Quotient poly ideal
modIdeal :: poly -> Quotient poly ideal
modIdeal = Proxy ideal -> poly -> Quotient poly ideal
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
Proxy ideal -> poly -> Quotient poly ideal
modIdeal' (Proxy ideal
forall k (t :: k). Proxy t
Proxy :: Proxy ideal)
gBasis' ::
(Reifies ideal (QIdeal poly)) =>
Proxy ideal ->
[poly]
gBasis' :: Proxy ideal -> [poly]
gBasis' Proxy ideal
pxy = QIdeal poly -> [poly]
forall poly. QIdeal poly -> [poly]
_gBasis (Proxy ideal -> QIdeal poly
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect Proxy ideal
pxy)
{-# SPECIALIZE INLINE gBasis' ::
(Reifies ideal (QIdeal (OrderedPolynomial r ord n))) =>
Proxy ideal ->
[OrderedPolynomial r ord n]
#-}
{-# SPECIALIZE INLINE gBasis' ::
(Reifies ideal (QIdeal (Unipol r))) =>
Proxy ideal ->
[Unipol r]
#-}
{-# INLINE gBasis' #-}
modIdeal' ::
( IsOrderedPolynomial poly
, Field (Coefficient poly)
, Reifies ideal (QIdeal poly)
) =>
Proxy ideal ->
poly ->
Quotient poly ideal
modIdeal' :: Proxy ideal -> poly -> Quotient poly ideal
modIdeal' Proxy ideal
pxy poly
f = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ poly
f poly -> [poly] -> poly
forall poly (t :: * -> *).
(IsOrderedPolynomial poly, Field (Coefficient poly), Functor t,
Foldable t) =>
poly -> t poly -> poly
`modPolynomial` QIdeal poly -> [poly]
forall poly. QIdeal poly -> [poly]
_gBasis (Proxy ideal -> QIdeal poly
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect Proxy ideal
pxy)
{-# SPECIALIZE INLINE modIdeal' ::
( IsMonomialOrder n ord
, CoeffRing r
, KnownNat n
, Field r
, Reifies ideal (QIdeal (OrderedPolynomial r ord n))
) =>
Proxy ideal ->
OrderedPolynomial r ord n ->
Quotient (OrderedPolynomial r ord n) ideal
#-}
{-# SPECIALIZE INLINE modIdeal' ::
( CoeffRing r
, Field r
, Reifies ideal (QIdeal (Unipol r))
) =>
Proxy ideal ->
Unipol r ->
Quotient (Unipol r) ideal
#-}
{-# INLINE modIdeal' #-}
buildQIdeal ::
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
Ideal poly ->
QIdeal poly
buildQIdeal :: Ideal poly -> QIdeal poly
buildQIdeal Ideal poly
ideal =
let bs :: [poly]
bs = (poly -> OrderedMonomial (MOrder poly) (Arity poly))
-> [poly] -> [poly]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn poly -> OrderedMonomial (MOrder poly) (Arity poly)
forall poly.
IsOrderedPolynomial poly =>
poly -> OrderedMonomial (MOrder poly) (Arity poly)
leadingMonomial ([poly] -> [poly]) -> [poly] -> [poly]
forall a b. (a -> b) -> a -> b
$! Ideal poly -> [poly]
forall poly.
(Field (Coefficient poly), IsOrderedPolynomial poly) =>
Ideal poly -> [poly]
calcGroebnerBasis Ideal poly
ideal
in case [poly] -> Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
forall poly.
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
[poly] -> Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
stdMonoms [poly]
bs of
Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
Nothing -> [poly] -> QIdeal poly
forall poly. [poly] -> QIdeal poly
QIdeal [poly]
bs
Just [OrderedMonomial (MOrder poly) (Arity poly)]
ms -> [poly]
-> [OrderedMonomial (MOrder poly) (Arity poly)]
-> Table poly
-> QIdeal poly
forall poly.
[poly]
-> [OrderedMonomial (MOrder poly) (Arity poly)]
-> Table poly
-> QIdeal poly
ZeroDimIdeal [poly]
bs [OrderedMonomial (MOrder poly) (Arity poly)]
ms ([poly]
-> [OrderedMonomial (MOrder poly) (Arity poly)] -> Table poly
forall poly.
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
[poly]
-> [OrderedMonomial (MOrder poly) (Arity poly)] -> Table poly
buildMultTable [poly]
bs [OrderedMonomial (MOrder poly) (Arity poly)]
ms)
{-# SPECIALIZE INLINE buildQIdeal ::
(IsMonomialOrder n ord, CoeffRing r, KnownNat n, Field r) =>
Ideal (OrderedPolynomial r ord n) ->
QIdeal (OrderedPolynomial r ord n)
#-}
{-# SPECIALIZE INLINE buildQIdeal ::
(CoeffRing r, Field r) =>
Ideal (Unipol r) ->
QIdeal (Unipol r)
#-}
{-# INLINE buildQIdeal #-}
reifyQuotient ::
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
Ideal poly ->
(forall (ideal :: Type). Reifies ideal (QIdeal poly) => Proxy ideal -> a) ->
a
reifyQuotient :: Ideal poly
-> (forall ideal. Reifies ideal (QIdeal poly) => Proxy ideal -> a)
-> a
reifyQuotient Ideal poly
ideal = QIdeal poly
-> (forall ideal. Reifies ideal (QIdeal poly) => Proxy ideal -> a)
-> a
forall a r. a -> (forall s. Reifies s a => Proxy s -> r) -> r
reify (Ideal poly -> QIdeal poly
forall poly.
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
Ideal poly -> QIdeal poly
buildQIdeal Ideal poly
ideal)
{-# INLINE reifyQuotient #-}
withQuotient ::
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
Ideal poly ->
(forall (ideal :: Type). Reifies ideal (QIdeal poly) => Quotient poly ideal) ->
poly
withQuotient :: Ideal poly
-> (forall ideal.
Reifies ideal (QIdeal poly) =>
Quotient poly ideal)
-> poly
withQuotient Ideal poly
ideal forall ideal. Reifies ideal (QIdeal poly) => Quotient poly ideal
v = Ideal poly
-> (forall ideal.
Reifies ideal (QIdeal poly) =>
Proxy ideal -> poly)
-> poly
forall poly a.
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
Ideal poly
-> (forall ideal. Reifies ideal (QIdeal poly) => Proxy ideal -> a)
-> a
reifyQuotient Ideal poly
ideal (Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ (Quotient poly ideal -> poly)
-> (Proxy ideal -> Quotient poly ideal) -> Proxy ideal -> poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Quotient poly ideal -> Proxy ideal -> Quotient poly ideal
forall k (f :: k -> *) (s :: k). f s -> Proxy s -> f s
asProxyOf Quotient poly ideal
forall ideal. Reifies ideal (QIdeal poly) => Quotient poly ideal
v)
{-# INLINE withQuotient #-}
asProxyOf :: f s -> Proxy s -> f s
asProxyOf :: f s -> Proxy s -> f s
asProxyOf f s
a Proxy s
_ = f s
a
{-# INLINE asProxyOf #-}
deriving instance Additive poly => Additive (Quotient poly ideal)
deriving instance Monoidal poly => Monoidal (Quotient poly ideal)
deriving instance Group poly => Group (Quotient poly ideal)
deriving instance Abelian poly => Abelian (Quotient poly ideal)
instance
Monoidal poly =>
LeftModule Natural (Quotient poly ideal)
where
Natural
r .* :: Natural -> Quotient poly ideal -> Quotient poly ideal
.* Quotient poly ideal
f = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ Natural
r Natural -> poly -> poly
forall r m. LeftModule r m => r -> m -> m
.* Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f
instance
Monoidal poly =>
RightModule Natural (Quotient poly ideal)
where
Quotient poly ideal
f *. :: Quotient poly ideal -> Natural -> Quotient poly ideal
*. Natural
r = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ Natural
r Natural -> poly -> poly
forall r m. LeftModule r m => r -> m -> m
.* Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f
instance
Group poly =>
LeftModule Integer (Quotient poly ideal)
where
Integer
r .* :: Integer -> Quotient poly ideal -> Quotient poly ideal
.* Quotient poly ideal
f = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ Integer
r Integer -> poly -> poly
forall r m. LeftModule r m => r -> m -> m
.* Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f
instance
Group poly =>
RightModule Integer (Quotient poly ideal)
where
Quotient poly ideal
f *. :: Quotient poly ideal -> Integer -> Quotient poly ideal
*. Integer
r = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ Integer
r Integer -> poly -> poly
forall r m. LeftModule r m => r -> m -> m
.* Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f
instance
(Field (Coefficient poly), IsOrderedPolynomial poly, Reifies ideal (QIdeal poly)) =>
Multiplicative (Quotient poly ideal)
where
Quotient poly ideal
f * :: Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
* Quotient poly ideal
g = poly -> Quotient poly ideal
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
poly -> Quotient poly ideal
modIdeal (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f poly -> poly -> poly
forall r. Multiplicative r => r -> r -> r
* Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
g
instance
(Field (Coefficient poly), IsOrderedPolynomial poly, Reifies ideal (QIdeal poly)) =>
Semiring (Quotient poly ideal)
instance
(Field (Coefficient poly), IsOrderedPolynomial poly, Reifies ideal (QIdeal poly)) =>
Unital (Quotient poly ideal)
where
one :: Quotient poly ideal
one = poly -> Quotient poly ideal
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
poly -> Quotient poly ideal
modIdeal poly
forall r. Unital r => r
one
instance
( Field (Coefficient poly)
, IsOrderedPolynomial poly
, Reifies ideal (QIdeal poly)
) =>
Rig (Quotient poly ideal)
instance
( Field (Coefficient poly)
, IsOrderedPolynomial poly
, Reifies ideal (QIdeal poly)
) =>
Ring (Quotient poly ideal)
instance
( r ~ (Coefficient poly)
, Field (Coefficient poly)
, IsOrderedPolynomial poly
) =>
LeftModule (Scalar r) (Quotient poly ideal)
where
Scalar r
r .* :: Scalar r -> Quotient poly ideal -> Quotient poly ideal
.* Quotient poly ideal
f = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ Scalar r
r Scalar r -> poly -> poly
forall r m. LeftModule r m => r -> m -> m
.* Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f
instance
(r ~ (Coefficient poly), IsOrderedPolynomial poly) =>
RightModule (Scalar r) (Quotient poly ideal)
where
Quotient poly ideal
f *. :: Quotient poly ideal -> Scalar r -> Quotient poly ideal
*. Scalar r
r = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal) -> poly -> Quotient poly ideal
forall a b. (a -> b) -> a -> b
$ Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_ Quotient poly ideal
f poly -> Scalar r -> poly
forall r m. RightModule r m => m -> r -> m
*. Scalar r
r
instance
( Field (Coefficient poly)
, UnitNormalForm poly
, IsOrderedPolynomial poly
, Reifies ideal (QIdeal poly)
) =>
P.Num (Quotient poly ideal)
where
+ :: Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
(+) = Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
forall r. Additive r => r -> r -> r
(NA.+)
* :: Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
(*) = Quotient poly ideal -> Quotient poly ideal -> Quotient poly ideal
forall r. Multiplicative r => r -> r -> r
(NA.*)
fromInteger :: Integer -> Quotient poly ideal
fromInteger = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal)
-> (Integer -> poly) -> Integer -> Quotient poly ideal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapAlgebra poly -> poly
forall a. WrapAlgebra a -> a
unwrapAlgebra (WrapAlgebra poly -> poly)
-> (Integer -> WrapAlgebra poly) -> Integer -> poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> WrapAlgebra poly
forall a. Num a => Integer -> a
P.fromInteger
signum :: Quotient poly ideal -> Quotient poly ideal
signum = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal)
-> (Quotient poly ideal -> poly)
-> Quotient poly ideal
-> Quotient poly ideal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapAlgebra poly -> poly
forall a. WrapAlgebra a -> a
unwrapAlgebra (WrapAlgebra poly -> poly)
-> (Quotient poly ideal -> WrapAlgebra poly)
-> Quotient poly ideal
-> poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapAlgebra poly -> WrapAlgebra poly
forall a. Num a => a -> a
P.signum (WrapAlgebra poly -> WrapAlgebra poly)
-> (Quotient poly ideal -> WrapAlgebra poly)
-> Quotient poly ideal
-> WrapAlgebra poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. poly -> WrapAlgebra poly
forall a. a -> WrapAlgebra a
WrapAlgebra (poly -> WrapAlgebra poly)
-> (Quotient poly ideal -> poly)
-> Quotient poly ideal
-> WrapAlgebra poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_
abs :: Quotient poly ideal -> Quotient poly ideal
abs = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal)
-> (Quotient poly ideal -> poly)
-> Quotient poly ideal
-> Quotient poly ideal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapAlgebra poly -> poly
forall a. WrapAlgebra a -> a
unwrapAlgebra (WrapAlgebra poly -> poly)
-> (Quotient poly ideal -> WrapAlgebra poly)
-> Quotient poly ideal
-> poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapAlgebra poly -> WrapAlgebra poly
forall a. Num a => a -> a
P.abs (WrapAlgebra poly -> WrapAlgebra poly)
-> (Quotient poly ideal -> WrapAlgebra poly)
-> Quotient poly ideal
-> WrapAlgebra poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. poly -> WrapAlgebra poly
forall a. a -> WrapAlgebra a
WrapAlgebra (poly -> WrapAlgebra poly)
-> (Quotient poly ideal -> poly)
-> Quotient poly ideal
-> WrapAlgebra poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_
negate :: Quotient poly ideal -> Quotient poly ideal
negate = poly -> Quotient poly ideal
forall k poly (ideal :: k). poly -> Quotient poly ideal
Quotient (poly -> Quotient poly ideal)
-> (Quotient poly ideal -> poly)
-> Quotient poly ideal
-> Quotient poly ideal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapAlgebra poly -> poly
forall a. WrapAlgebra a -> a
unwrapAlgebra (WrapAlgebra poly -> poly)
-> (Quotient poly ideal -> WrapAlgebra poly)
-> Quotient poly ideal
-> poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapAlgebra poly -> WrapAlgebra poly
forall a. Num a => a -> a
P.negate (WrapAlgebra poly -> WrapAlgebra poly)
-> (Quotient poly ideal -> WrapAlgebra poly)
-> Quotient poly ideal
-> WrapAlgebra poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. poly -> WrapAlgebra poly
forall a. a -> WrapAlgebra a
WrapAlgebra (poly -> WrapAlgebra poly)
-> (Quotient poly ideal -> poly)
-> Quotient poly ideal
-> WrapAlgebra poly
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Quotient poly ideal -> poly
forall poly k (ideal :: k). Quotient poly ideal -> poly
quotRepr_
reduce ::
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
poly ->
Ideal poly ->
poly
reduce :: poly -> Ideal poly -> poly
reduce poly
f Ideal poly
i = Ideal poly
-> (forall ideal.
Reifies ideal (QIdeal poly) =>
Quotient poly ideal)
-> poly
forall poly.
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
Ideal poly
-> (forall ideal.
Reifies ideal (QIdeal poly) =>
Quotient poly ideal)
-> poly
withQuotient Ideal poly
i ((forall ideal. Reifies ideal (QIdeal poly) => Quotient poly ideal)
-> poly)
-> (forall ideal.
Reifies ideal (QIdeal poly) =>
Quotient poly ideal)
-> poly
forall a b. (a -> b) -> a -> b
$ poly -> Quotient poly ideal
forall k poly (ideal :: k).
(IsOrderedPolynomial poly, Field (Coefficient poly),
Reifies ideal (QIdeal poly)) =>
poly -> Quotient poly ideal
modIdeal poly
f
{-# SPECIALIZE INLINE reduce ::
(IsMonomialOrder n ord, CoeffRing r, KnownNat n, Field r) =>
OrderedPolynomial r ord n ->
Ideal (OrderedPolynomial r ord n) ->
OrderedPolynomial r ord n
#-}
{-# SPECIALIZE INLINE reduce ::
(CoeffRing r, Field r) =>
Unipol r ->
Ideal (Unipol r) ->
Unipol r
#-}
{-# INLINE reduce #-}
isZeroDimensional ::
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
[poly] ->
Bool
isZeroDimensional :: [poly] -> Bool
isZeroDimensional [poly]
ii = Maybe [OrderedMonomial (MOrder poly) (Arity poly)] -> Bool
forall a. Maybe a -> Bool
isJust (Maybe [OrderedMonomial (MOrder poly) (Arity poly)] -> Bool)
-> Maybe [OrderedMonomial (MOrder poly) (Arity poly)] -> Bool
forall a b. (a -> b) -> a -> b
$ [poly] -> Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
forall poly.
(IsOrderedPolynomial poly, Field (Coefficient poly)) =>
[poly] -> Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
stdMonoms ([poly] -> Maybe [OrderedMonomial (MOrder poly) (Arity poly)])
-> [poly] -> Maybe [OrderedMonomial (MOrder poly) (Arity poly)]
forall a b. (a -> b) -> a -> b
$ Ideal poly -> [poly]
forall poly.
(Field (Coefficient poly), IsOrderedPolynomial poly) =>
Ideal poly -> [poly]
calcGroebnerBasis (Ideal poly -> [poly]) -> Ideal poly -> [poly]
forall a b. (a -> b) -> a -> b
$ [poly] -> Ideal poly
forall r. (DecidableZero r, Monoidal r) => [r] -> Ideal r
toIdeal [poly]
ii
{-# INLINE isZeroDimensional #-}