Rename *ll* and *ul* to ll and ul in in-interval
[maxima.git] / share / contrib / Grobner / grobner.lisp
blobc06469af59468e7b23ca7327b1eae52eaaa3b41e
1 ;;; -*- Mode: Lisp; Package: Maxima; Syntax: Common-Lisp; Base: 10 -*-
2 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
3 ;;;
4 ;;; $Id: grobner.lisp,v 1.6 2009-06-02 07:49:49 andrejv Exp $
5 ;;; Copyright (C) 1999, 2002 Marek Rychlik <rychlik@u.arizona.edu>
6 ;;;
7 ;;; This program is free software; you can redistribute it and/or modify
8 ;;; it under the terms of the GNU General Public License as published by
9 ;;; the Free Software Foundation; either version 2 of the License, or
10 ;;; (at your option) any later version.
11 ;;;
12 ;;; This program is distributed in the hope that it will be useful,
13 ;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
14 ;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 ;;; GNU General Public License for more details.
16 ;;;
17 ;;; You should have received a copy of the GNU General Public License
18 ;;; along with this program; if not, write to the Free Software
19 ;;; Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA
20 ;;;
21 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23 (in-package :maxima)
25 (macsyma-module cgb-maxima)
27 ;; Macros for making lists with iterators - an exammple of GENSYM
28 ;; GROBNER-MAKELIST-1 makes a list with one iterator, while GROBNER-MAKELIST accepts an
29 ;; arbitrary number of iterators
31 ;; Sample usage:
32 ;; Without a step:
33 ;; >(grobner-makelist-1 (* 2 i) i 0 10)
34 ;; (0 2 4 6 8 10 12 14 16 18 20)
35 ;; With a step of 3:
36 ;; >(grobner-makelist-1 (* 2 i) i 0 10 3)
37 ;; (0 6 12 18)
39 ;; Generate sums of squares of numbers between 1 and 4:
40 ;; >(grobner-makelist (+ (* i i) (* j j)) (i 1 4) (j 1 i))
41 ;; (2 5 8 10 13 18 17 20 25 32)
42 ;; >(grobner-makelist (list i j '---> (+ (* i i) (* j j))) (i 1 4) (j 1 i))
43 ;; ((1 1 ---> 2) (2 1 ---> 5) (2 2 ---> 8) (3 1 ---> 10) (3 2 ---> 13)
44 ;; (3 3 ---> 18) (4 1 ---> 17) (4 2 ---> 20) (4 3 ---> 25) (4 4 ---> 32))
46 ;; Evaluate expression expr with variable set to lo, lo+1,... ,hi
47 ;; and put the results in a list.
48 (defmacro grobner-makelist-1 (expr var lo hi &optional (step 1))
49 (let ((l (gensym)))
50 `(do ((,var ,lo (+ ,var ,step))
51 (,l nil (cons ,expr ,l)))
52 ((> ,var ,hi) (reverse ,l))
53 (declare (fixnum ,var)))))
55 (defmacro grobner-makelist (expr (var lo hi &optional (step 1)) &rest more)
56 (if (endp more)
57 `(grobner-makelist-1 ,expr ,var ,lo ,hi ,step)
58 (let* ((l (gensym)))
59 `(do ((,var ,lo (+ ,var ,step))
60 (,l nil (nconc ,l `,(grobner-makelist ,expr ,@more))))
61 ((> ,var ,hi) ,l)
62 (declare (fixnum ,var))))))
64 ;;----------------------------------------------------------------
65 ;; This package implements BASIC OPERATIONS ON MONOMIALS
66 ;;----------------------------------------------------------------
67 ;; DATA STRUCTURES: Monomials are represented as lists:
69 ;; monom: (n1 n2 ... nk) where ni are non-negative integers
71 ;; However, lists may be implemented as other sequence types,
72 ;; so the flexibility to change the representation should be
73 ;; maintained in the code to use general operations on sequences
74 ;; whenever possible. The optimization for the actual representation
75 ;; should be left to declarations and the compiler.
76 ;;----------------------------------------------------------------
77 ;; EXAMPLES: Suppose that variables are x and y. Then
79 ;; Monom x*y^2 ---> (1 2)
81 ;;----------------------------------------------------------------
83 (deftype exponent ()
84 "Type of exponent in a monomial."
85 'fixnum)
87 (deftype monom (&optional dim)
88 "Type of monomial."
89 `(simple-array exponent (,dim)))
91 (declaim (optimize (speed 3) (safety 1)))
93 (declaim (ftype (function (monom) fixnum) monom-dimension monom-sugar)
94 (ftype (function (monom &optional fixnum fixnum) fixnum) monom-total-degree)
95 (ftype (function (monom monom) monom) monom-div monom-mul monom-lcm monom-gcd)
96 (ftype (function (monom monom) (member t nil)) monom-divides-p monom-divisible-by-p monom-rel-prime-p)
97 (ftype (function (monom monom monom) (member t nil)) monom-divides-monom-lcm-p)
98 (ftype (function (monom monom monom monom) (member t nil)) monom-lcm-divides-monom-lcm-p)
99 (ftype (function (monom fixnum) (member t nil)) monom-depends-p)
100 ;;(ftype (function (t monom &optional monom) monom) monom-map)
101 ;;(ftype (function (monom monom) monom) monom-append)
104 (declaim (inline monom-mul monom-div
105 monom-total-degree monom-divides-p
106 monom-divisible-by-p monom-rel-prime monom-lcm))
108 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
110 ;; Construction of monomials
112 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
114 (defmacro make-monom (dim &key (initial-contents nil initial-contents-supplied-p)
115 (initial-element 0 initial-element-supplied-p))
116 "Make a monomial with DIM variables. Additional argument
117 INITIAL-CONTENTS specifies the list of powers of the consecutive
118 variables. The alternative additional argument INITIAL-ELEMENT
119 specifies the common power for all variables."
120 ;(declare (fixnum dim))
121 `(make-array ,dim
122 :element-type 'exponent
123 ,@(when initial-contents-supplied-p `(:initial-contents ,initial-contents))
124 ,@(when initial-element-supplied-p `(:initial-element ,initial-element))))
127 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
129 ;; Operations on monomials
131 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
133 (defmacro monom-elt (m index)
134 "Return the power in the monomial M of variable number INDEX."
135 `(elt ,m ,index))
137 (defun monom-dimension (m)
138 "Return the number of variables in the monomial M."
139 (length m))
141 (defun monom-total-degree (m &optional (start 0) (end (length m)))
142 "Return the todal degree of a monomoal M. Optionally, a range
143 of variables may be specified with arguments START and END."
144 (declare (type monom m) (fixnum start end))
145 (reduce #'+ m :start start :end end))
147 (defun monom-sugar (m &aux (start 0) (end (length m)))
148 "Return the sugar of a monomial M. Optionally, a range
149 of variables may be specified with arguments START and END."
150 (declare (type monom m) (fixnum start end))
151 (monom-total-degree m start end))
153 (defun monom-div (m1 m2 &aux (result (copy-seq m1)))
154 "Divide monomial M1 by monomial M2."
155 (declare (type monom m1 m2 result))
156 (map-into result #'- m1 m2))
158 (defun monom-mul (m1 m2 &aux (result (copy-seq m1)))
159 "Multiply monomial M1 by monomial M2."
160 (declare (type monom m1 m2 result))
161 (map-into result #'+ m1 m2))
163 (defun monom-divides-p (m1 m2)
164 "Returns T if monomial M1 divides monomial M2, NIL otherwise."
165 (declare (type monom m1 m2))
166 (every #'<= m1 m2))
168 (defun monom-divides-monom-lcm-p (m1 m2 m3)
169 "Returns T if monomial M1 divides MONOM-LCM(M2,M3), NIL otherwise."
170 (declare (type monom m1 m2 m3))
171 (every #'(lambda (x y z) (declare (type exponent x y z)) (<= x (max y z))) m1 m2 m3))
173 (defun monom-lcm-divides-monom-lcm-p (m1 m2 m3 m4)
174 "Returns T if monomial MONOM-LCM(M1,M2) divides MONOM-LCM(M3,M4), NIL otherwise."
175 (declare (type monom m1 m2 m3 m4))
176 (every #'(lambda (x y z w) (declare (type exponent x y z w)) (<= (max x y) (max z w))) m1 m2 m3 m4))
178 (defun monom-lcm-equal-monom-lcm-p (m1 m2 m3 m4)
179 "Returns T if monomial MONOM-LCM(M1,M2) equals MONOM-LCM(M3,M4), NIL otherwise."
180 (declare (type monom m1 m2 m3 m4))
181 (every #'(lambda (x y z w) (declare (type exponent x y z w)) (= (max x y) (max z w))) m1 m2 m3 m4))
183 (defun monom-divisible-by-p (m1 m2)
184 "Returns T if monomial M1 is divisible by monomial M2, NIL otherwise."
185 (declare (type monom m1 m2))
186 (every #'>= m1 m2))
188 (defun monom-rel-prime-p (m1 m2)
189 "Returns T if two monomials M1 and M2 are relatively prime (disjoint)."
190 (declare (type monom m1 m2))
191 (every #'(lambda (x y) (declare (type exponent x y)) (zerop (min x y))) m1 m2))
193 (defun monom-equal-p (m1 m2)
194 "Returns T if two monomials M1 and M2 are equal."
195 (declare (type monom m1 m2))
196 (every #'= m1 m2))
198 (defun monom-lcm (m1 m2 &aux (result (copy-seq m1)))
199 "Returns least common multiple of monomials M1 and M2."
200 (declare (type monom m1 m2))
201 (map-into result #'max m1 m2))
203 (defun monom-gcd (m1 m2 &aux (result (copy-seq m1)))
204 "Returns greatest common divisor of monomials M1 and M2."
205 (declare (type monom m1 m2))
206 (map-into result #'min m1 m2))
208 (defun monom-depends-p (m k)
209 "Return T if the monomial M depends on variable number K."
210 (declare (type monom m) (fixnum k))
211 (plusp (elt m k)))
213 (defmacro monom-map (fun m &rest ml &aux (result `(copy-seq ,m)))
214 `(map-into ,result ,fun ,m ,@ml))
216 (defmacro monom-append (m1 m2)
217 `(concatenate 'monom ,m1 ,m2))
219 (defmacro monom-contract (k m)
220 `(subseq ,m ,k))
222 (defun monom-exponents (m)
223 (declare (type monom m))
224 (coerce m 'list))
227 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
229 ;; Implementations of various admissible monomial orders
231 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
233 ;; pure lexicographic
234 (defun lex> (p q &optional (start 0) (end (monom-dimension p)))
235 "Return T if P>Q with respect to lexicographic order, otherwise NIL.
236 The second returned value is T if P=Q, otherwise it is NIL."
237 (declare (type monom p q) (type fixnum start end))
238 (do ((i start (1+ i)))
239 ((>= i end) (values nil t))
240 (declare (type fixnum i))
241 (cond
242 ((> (monom-elt p i) (monom-elt q i))
243 (return-from lex> (values t nil)))
244 ((< (monom-elt p i) (monom-elt q i))
245 (return-from lex> (values nil nil))))))
247 ;; total degree order , ties broken by lexicographic
248 (defun grlex> (p q &optional (start 0) (end (monom-dimension p)))
249 "Return T if P>Q with respect to graded lexicographic order, otherwise NIL.
250 The second returned value is T if P=Q, otherwise it is NIL."
251 (declare (type monom p q) (type fixnum start end))
252 (let ((d1 (monom-total-degree p start end))
253 (d2 (monom-total-degree q start end)))
254 (cond
255 ((> d1 d2) (values t nil))
256 ((< d1 d2) (values nil nil))
258 (lex> p q start end)))))
261 ;; total degree, ties broken by reverse lexicographic
262 (defun grevlex> (p q &optional (start 0) (end (monom-dimension p)))
263 "Return T if P>Q with respect to graded reverse lexicographic order,
264 NIL otherwise. The second returned value is T if P=Q, otherwise it is NIL."
265 (declare (type monom p q) (type fixnum start end))
266 (let ((d1 (monom-total-degree p start end))
267 (d2 (monom-total-degree q start end)))
268 (cond
269 ((> d1 d2) (values t nil))
270 ((< d1 d2) (values nil nil))
272 (revlex> p q start end)))))
275 ;; reverse lexicographic
276 (defun revlex> (p q &optional (start 0) (end (monom-dimension p)))
277 "Return T if P>Q with respect to reverse lexicographic order, NIL
278 otherwise. The second returned value is T if P=Q, otherwise it is
279 NIL. This is not and admissible monomial order because some sets do
280 not have a minimal element. This order is useful in constructing other
281 orders."
282 (declare (type monom p q) (type fixnum start end))
283 (do ((i (1- end) (1- i)))
284 ((< i start) (values nil t))
285 (declare (type fixnum i))
286 (cond
287 ((< (monom-elt p i) (monom-elt q i))
288 (return-from revlex> (values t nil)))
289 ((> (monom-elt p i) (monom-elt q i))
290 (return-from revlex> (values nil nil))))))
293 (defun invlex> (p q &optional (start 0) (end (monom-dimension p)))
294 "Return T if P>Q with respect to inverse lexicographic order, NIL otherwise
295 The second returned value is T if P=Q, otherwise it is NIL."
296 (declare (type monom p q) (type fixnum start end))
297 (do ((i (1- end) (1- i)))
298 ((< i start) (values nil t))
299 (declare (type fixnum i))
300 (cond
301 ((> (monom-elt p i) (monom-elt q i))
302 (return-from invlex> (values t nil)))
303 ((< (monom-elt p i) (monom-elt q i))
304 (return-from invlex> (values nil nil))))))
307 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
309 ;; Order making functions
311 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
313 (declaim (type function *monomial-order* *primary-elimination-order* *secondary-elimination-order*))
315 (defvar *monomial-order* #'lex>
316 "Default order for monomial comparisons")
318 (defmacro monomial-order (x y)
319 `(funcall *monomial-order* ,x ,y))
321 (defun reverse-monomial-order (x y)
322 (monomial-order y x))
324 (defvar *primary-elimination-order* #'lex>)
326 (defvar *secondary-elimination-order* #'lex>)
328 (defvar *elimination-order* nil
329 "Default elimination order used in elimination-based functions.
330 If not NIL, it is assumed to be a proper elimination order. If NIL,
331 we will construct an elimination order using the values of
332 *PRIMARY-ELIMINATION-ORDER* and *SECONDARY-ELIMINATION-ORDER*.")
334 (defun elimination-order (k)
335 "Return a predicate which compares monomials according to the
336 K-th elimination order. Two variables *PRIMARY-ELIMINATION-ORDER*
337 and *SECONDARY-ELIMINATION-ORDER* control the behavior on the first K
338 and the remaining variables, respectively."
339 (declare (type fixnum k))
340 #'(lambda (p q &optional (start 0) (end (monom-dimension p)))
341 (declare (type monom p q) (type fixnum start end))
342 (multiple-value-bind (primary equal)
343 (funcall *primary-elimination-order* p q start k)
344 (if equal
345 (funcall *secondary-elimination-order* p q k end)
346 (values primary nil)))))
348 (defun elimination-order-1 (p q &optional (start 0) (end (monom-dimension p)))
349 "Equivalent to the function returned by the call to (ELIMINATION-ORDER 1)."
350 (declare (type monom p q) (type fixnum start end))
351 (cond
352 ((> (monom-elt p start) (monom-elt q start)) (values t nil))
353 ((< (monom-elt p start) (monom-elt q start)) (values nil nil))
354 (t (funcall *secondary-elimination-order* p q (1+ start) end))))
357 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
359 ;; Priority queue stuff
361 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
363 (declaim (integer *priority-queue-allocation-size*))
365 (defparameter *priority-queue-allocation-size* 16)
367 (defun priority-queue-make-heap (&key (element-type 'fixnum))
368 (make-array *priority-queue-allocation-size* :element-type element-type :fill-pointer 1
369 :adjustable t))
371 (defstruct (priority-queue (:constructor priority-queue-construct))
372 (heap (priority-queue-make-heap))
373 test)
375 (defun make-priority-queue (&key (element-type 'fixnum)
376 (test #'<=)
377 (element-key #'identity))
378 (priority-queue-construct
379 :heap (priority-queue-make-heap :element-type element-type)
380 :test #'(lambda (x y) (funcall test (funcall element-key y) (funcall element-key x)))))
382 (defun priority-queue-insert (pq item)
383 (priority-queue-heap-insert (priority-queue-heap pq) item (priority-queue-test pq)))
385 (defun priority-queue-remove (pq)
386 (priority-queue-heap-remove (priority-queue-heap pq) (priority-queue-test pq)))
388 (defun priority-queue-empty-p (pq)
389 (priority-queue-heap-empty-p (priority-queue-heap pq)))
391 (defun priority-queue-size (pq)
392 (fill-pointer (priority-queue-heap pq)))
394 (defun priority-queue-upheap (a k
395 &optional
396 (test #'<=)
397 &aux (v (aref a k)))
398 (declare (fixnum k))
399 (assert (< 0 k (fill-pointer a)))
400 (loop
401 (let ((parent (ash k -1)))
402 (when (zerop parent) (return))
403 (unless (funcall test (aref a parent) v)
404 (return))
405 (setf (aref a k) (aref a parent)
406 k parent)))
407 (setf (aref a k) v)
411 (defun priority-queue-heap-insert (a item &optional (test #'<=))
412 (vector-push-extend item a)
413 (priority-queue-upheap a (1- (fill-pointer a)) test))
415 (defun priority-queue-downheap (a k
416 &optional
417 (test #'<=)
418 &aux (v (aref a k)) (j 0) (n (fill-pointer a)))
419 (declare (fixnum k n j))
420 (loop
421 (unless (<= k (ash n -1))
422 (return))
423 (setf j (ash k 1))
424 (if (and (< j n) (not (funcall test (aref a (1+ j)) (aref a j))))
425 (incf j))
426 (when (funcall test (aref a j) v)
427 (return))
428 (setf (aref a k) (aref a j)
429 k j))
430 (setf (aref a k) v)
433 (defun priority-queue-heap-remove (a &optional (test #'<=) &aux (v (aref a 1)))
434 (when (<= (fill-pointer a) 1) (error "Empty queue."))
435 (setf (aref a 1) (vector-pop a))
436 (priority-queue-downheap a 1 test)
437 (values v a))
439 (defun priority-queue-heap-empty-p (a)
440 (<= (fill-pointer a) 1))
443 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
445 ;; Global switches
446 ;; (Can be used in Maxima just fine)
448 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
450 (defmvar $poly_monomial_order '$lex
451 "This switch controls which monomial order is used in polynomial
452 and Grobner basis calculations. If not set, LEX will be used")
454 (defmvar $poly_coefficient_ring '$expression_ring
455 "This switch indicates the coefficient ring of the polynomials
456 that will be used in grobner calculations. If not set, Maxima's
457 general expression ring will be used. This variable may be set
458 to RING_OF_INTEGERS if desired.")
460 (defmvar $poly_primary_elimination_order nil
461 "Name of the default order for eliminated variables in elimination-based functions.
462 If not set, LEX will be used.")
464 (defmvar $poly_secondary_elimination_order nil
465 "Name of the default order for kept variables in elimination-based functions.
466 If not set, LEX will be used.")
468 (defmvar $poly_elimination_order nil
469 "Name of the default elimination order used in elimination calculations.
470 If set, it overrides the settings in variables POLY_PRIMARY_ELIMINATION_ORDER
471 and SECONDARY_ELIMINATION_ORDER. The user must ensure that this is a true
472 elimination order valid for the number of eliminated variables.")
474 (defmvar $poly_return_term_list nil
475 "If set to T, all functions in this package will return each polynomial as a
476 list of terms in the current monomial order rather than a Maxima general expression.")
478 (defmvar $poly_grobner_debug nil
479 "If set to TRUE, produce debugging and tracing output.")
481 (defmvar $poly_grobner_algorithm '$buchberger
482 "The name of the algorithm used to find grobner bases.")
484 (defmvar $poly_top_reduction_only nil
485 "If not FALSE, use top reduction only whenever possible.
486 Top reduction means that division algorithm stops after the first reduction.")
489 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
491 ;; Coefficient ring operations
493 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
495 ;; These are ALL operations that are performed on the coefficients by
496 ;; the package, and thus the coefficient ring can be changed by merely
497 ;; redefining these operations.
499 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
501 (defstruct (ring)
502 (parse #'identity :type function)
503 (unit #'identity :type function)
504 (zerop #'identity :type function)
505 (add #'identity :type function)
506 (sub #'identity :type function)
507 (uminus #'identity :type function)
508 (mul #'identity :type function)
509 (div #'identity :type function)
510 (lcm #'identity :type function)
511 (ezgcd #'identity :type function)
512 (gcd #'identity :type function))
514 (declaim (type ring *ring-of-integers* *FieldOfRationals*))
516 (defparameter *ring-of-integers*
517 (make-ring
518 :parse #'identity
519 :unit #'(lambda () 1)
520 :zerop #'zerop
521 :add #'+
522 :sub #'-
523 :uminus #'-
524 :mul #'*
525 :div #'/
526 :lcm #'lcm
527 :ezgcd #'(lambda (x y &aux (c (gcd x y))) (values c (/ x c) (/ y c)))
528 :gcd #'gcd)
529 "The ring of integers.")
532 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
534 ;; This is how we perform operations on coefficients
535 ;; using Maxima functions.
537 ;; Functions and macros dealing with internal representation structure
539 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
541 (defstruct (term
542 (:constructor make-term (monom coeff))
543 ;;(:type list)
545 (monom (make-monom 0) :type monom)
546 (coeff nil))
548 (defun make-term-variable (ring nvars pos
549 &optional
550 (power 1)
551 (coeff (funcall (ring-unit ring)))
552 &aux
553 (monom (make-monom nvars :initial-element 0)))
554 (declare (fixnum nvars pos power))
555 (incf (monom-elt monom pos) power)
556 (make-term monom coeff))
558 (defun term-sugar (term)
559 (monom-sugar (term-monom term)))
561 (defun termlist-sugar (p &aux (sugar -1))
562 (declare (fixnum sugar))
563 (dolist (term p sugar)
564 (setf sugar (max sugar (term-sugar term)))))
568 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
570 ;; Low-level polynomial arithmetic done on
571 ;; lists of terms
573 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
575 (defmacro termlist-lt (p) `(car ,p))
576 (defun termlist-lm (p) (term-monom (termlist-lt p)))
577 (defun termlist-lc (p) (term-coeff (termlist-lt p)))
579 (define-modify-macro scalar-mul (c) coeff-mul)
581 (declaim (ftype (function (ring t t) t) scalar-times-termlist))
583 (defun scalar-times-termlist (ring c p)
584 "Multiply scalar C by a polynomial P. This function works
585 even if there are divisors of 0."
586 (mapcan
587 #'(lambda (term)
588 (let ((c1 (funcall (ring-mul ring) c (term-coeff term))))
589 (unless (funcall (ring-zerop ring) c1)
590 (list (make-term (term-monom term) c1)))))
594 (declaim (ftype (function (ring term term) list) term-mul))
596 (defun term-mul (ring term1 term2)
597 "Returns (LIST TERM) whether TERM is the product of the terms TERM1 TERM2,
598 or NIL when the product is 0. This definition takes care of divisors of 0
599 in the coefficient ring."
600 (let ((c (funcall (ring-mul ring) (term-coeff term1) (term-coeff term2))))
601 (unless (funcall (ring-zerop ring) c)
602 (list (make-term (monom-mul (term-monom term1) (term-monom term2)) c)))))
604 (declaim (ftype (function (ring term list) list) term-times-termlist))
606 (defun term-times-termlist (ring term f)
607 (declare (type ring ring))
608 (mapcan #'(lambda (term-f) (term-mul ring term term-f)) f))
610 (declaim (ftype (function (ring list term) list) termlist-times-term))
612 (defun termlist-times-term (ring f term)
613 (mapcan #'(lambda (term-f) (term-mul ring term-f term)) f))
615 (declaim (ftype (function (monom term) term) monom-times-term))
617 (defun monom-times-term (m term)
618 (make-term (monom-mul m (term-monom term)) (term-coeff term)))
620 (declaim (ftype (function (monom list) list) monom-times-termlist))
622 (defun monom-times-termlist (m f)
623 (cond
624 ((null f) nil)
626 (mapcar #'(lambda (x) (monom-times-term m x)) f))))
628 (declaim (ftype (function (ring list) list) termlist-uminus))
630 (defun termlist-uminus (ring f)
631 (mapcar #'(lambda (x)
632 (make-term (term-monom x) (funcall (ring-uminus ring) (term-coeff x))))
635 (declaim (ftype (function (ring list list) list) termlist-add termlist-sub termlist-mul))
637 (defun termlist-add (ring p q)
638 (declare (type list p q))
639 (do (r)
640 ((cond
641 ((endp p)
642 (setf r (revappend r q)) t)
643 ((endp q)
644 (setf r (revappend r p)) t)
646 (multiple-value-bind
647 (lm-greater lm-equal)
648 (monomial-order (termlist-lm p) (termlist-lm q))
649 (cond
650 (lm-equal
651 (let ((s (funcall (ring-add ring) (termlist-lc p) (termlist-lc q))))
652 (unless (funcall (ring-zerop ring) s) ;check for cancellation
653 (setf r (cons (make-term (termlist-lm p) s) r)))
654 (setf p (cdr p) q (cdr q))))
655 (lm-greater
656 (setf r (cons (car p) r)
657 p (cdr p)))
658 (t (setf r (cons (car q) r)
659 q (cdr q)))))
660 nil))
661 r)))
663 (defun termlist-sub (ring p q)
664 (declare (type list p q))
665 (do (r)
666 ((cond
667 ((endp p)
668 (setf r (revappend r (termlist-uminus ring q)))
670 ((endp q)
671 (setf r (revappend r p))
674 (multiple-value-bind
675 (mgreater mequal)
676 (monomial-order (termlist-lm p) (termlist-lm q))
677 (cond
678 (mequal
679 (let ((s (funcall (ring-sub ring) (termlist-lc p) (termlist-lc q))))
680 (unless (funcall (ring-zerop ring) s) ;check for cancellation
681 (setf r (cons (make-term (termlist-lm p) s) r)))
682 (setf p (cdr p) q (cdr q))))
683 (mgreater
684 (setf r (cons (car p) r)
685 p (cdr p)))
686 (t (setf r (cons (make-term (termlist-lm q) (funcall (ring-uminus ring) (termlist-lc q))) r)
687 q (cdr q)))))
688 nil))
689 r)))
691 ;; Multiplication of polynomials
692 ;; Non-destructive version
693 (defun termlist-mul (ring p q)
694 (cond ((or (endp p) (endp q)) nil) ;p or q is 0 (represented by NIL)
695 ;; If p=p0+p1 and q=q0+q1 then pq=p0q0+p0q1+p1q
696 ((endp (cdr p))
697 (term-times-termlist ring (car p) q))
698 ((endp (cdr q))
699 (termlist-times-term ring p (car q)))
701 (let ((head (term-mul ring (termlist-lt p) (termlist-lt q)))
702 (tail (termlist-add ring (term-times-termlist ring (car p) (cdr q))
703 (termlist-mul ring (cdr p) q))))
704 (cond ((null head) tail)
705 ((null tail) head)
706 (t (nconc head tail)))))))
708 (defun termlist-unit (ring dimension)
709 (declare (fixnum dimension))
710 (list (make-term (make-monom dimension :initial-element 0)
711 (funcall (ring-unit ring)))))
713 (defun termlist-expt (ring poly n &aux (dim (monom-dimension (termlist-lm poly))))
714 (declare (type fixnum n dim))
715 (cond
716 ((minusp n) (error "termlist-expt: Negative exponent."))
717 ((endp poly) (if (zerop n) (termlist-unit ring dim) nil))
719 (do ((k 1 (ash k 1))
720 (q poly (termlist-mul ring q q)) ;keep squaring
721 (p (termlist-unit ring dim) (if (not (zerop (logand k n))) (termlist-mul ring p q) p)))
722 ((> k n) p)
723 (declare (fixnum k))))))
726 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
728 ;; Additional structure operations on a list of terms
730 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
732 (defun termlist-contract (p &optional (k 1))
733 "Eliminate first K variables from a polynomial P."
734 (mapcar #'(lambda (term) (make-term (monom-contract k (term-monom term))
735 (term-coeff term)))
738 (defun termlist-extend (p &optional (m (make-monom 1 :initial-element 0)))
739 "Extend every monomial in a polynomial P by inserting at the
740 beginning of every monomial the list of powers M."
741 (mapcar #'(lambda (term) (make-term (monom-append m (term-monom term))
742 (term-coeff term)))
745 (defun termlist-add-variables (p n)
746 "Add N variables to a polynomial P by inserting zero powers
747 at the beginning of each monomial."
748 (declare (fixnum n))
749 (mapcar #'(lambda (term)
750 (make-term (monom-append (make-monom n :initial-element 0)
751 (term-monom term))
752 (term-coeff term)))
756 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
758 ;; Arithmetic on polynomials
760 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
762 (defstruct (poly
763 ;;BOA constructor, by default constructs zero polynomial
764 (:constructor make-poly-from-termlist (termlist &optional (sugar (termlist-sugar termlist))))
765 (:constructor make-poly-zero (&aux (termlist nil) (sugar -1)))
766 ;;Constructor of polynomials representing a variable
767 (:constructor make-variable (ring nvars pos &optional (power 1)
768 &aux
769 (termlist (list
770 (make-term-variable ring nvars pos power)))
771 (sugar power)))
772 (:constructor poly-unit (ring dimension
773 &aux
774 (termlist (termlist-unit ring dimension))
775 (sugar 0))))
776 (termlist nil :type list)
777 (sugar -1 :type fixnum))
779 ;; Leading term
780 (defmacro poly-lt (p) `(car (poly-termlist ,p)))
782 ;; Second term
783 (defmacro poly-second-lt (p) `(cadar (poly-termlist ,p)))
785 ;; Leading monomial
786 (defun poly-lm (p) (term-monom (poly-lt p)))
788 ;; Second monomial
789 (defun poly-second-lm (p) (term-monom (poly-second-lt p)))
791 ;; Leading coefficient
792 (defun poly-lc (p) (term-coeff (poly-lt p)))
794 ;; Second coefficient
795 (defun poly-second-lc (p) (term-coeff (poly-second-lt p)))
797 ;; Testing for a zero polynomial
798 (defun poly-zerop (p) (null (poly-termlist p)))
800 ;; The number of terms
801 (defun poly-length (p) (length (poly-termlist p)))
803 (declaim (ftype (function (ring t poly) poly) scalar-times-poly))
805 (defun scalar-times-poly (ring c p)
806 (make-poly-from-termlist (scalar-times-termlist ring c (poly-termlist p)) (poly-sugar p)))
808 (declaim (ftype (function (monom poly) poly) monom-times-poly))
810 (defun monom-times-poly (m p)
811 (make-poly-from-termlist (monom-times-termlist m (poly-termlist p)) (+ (poly-sugar p) (monom-sugar m))))
813 (declaim (ftype (function (ring term poly) poly) term-times-poly))
815 (defun term-times-poly (ring term p)
816 (make-poly-from-termlist (term-times-termlist ring term (poly-termlist p)) (+ (poly-sugar p) (term-sugar term))))
818 (declaim (ftype (function (ring poly poly) poly) poly-add poly-sub poly-mul))
820 (defun poly-add (ring p q)
821 (make-poly-from-termlist (termlist-add ring (poly-termlist p) (poly-termlist q)) (max (poly-sugar p) (poly-sugar q))))
823 (defun poly-sub (ring p q)
824 (make-poly-from-termlist (termlist-sub ring (poly-termlist p) (poly-termlist q)) (max (poly-sugar p) (poly-sugar q))))
826 (declaim (ftype (function (ring poly) poly) poly-uminus))
828 (defun poly-uminus (ring p)
829 (make-poly-from-termlist (termlist-uminus ring (poly-termlist p)) (poly-sugar p)))
831 (defun poly-mul (ring p q)
832 (make-poly-from-termlist (termlist-mul ring (poly-termlist p) (poly-termlist q)) (+ (poly-sugar p) (poly-sugar q))))
834 (declaim (ftype (function (ring poly fixnum) poly) poly-expt))
836 (defun poly-expt (ring p n)
837 (make-poly-from-termlist (termlist-expt ring (poly-termlist p) n) (* n (poly-sugar p))))
839 (defun poly-append (&rest plist)
840 (make-poly-from-termlist (apply #'append (mapcar #'poly-termlist plist))
841 (apply #'max (mapcar #'poly-sugar plist))))
843 (declaim (ftype (function (poly) poly) poly-nreverse))
845 (defun poly-nreverse (p)
846 (setf (poly-termlist p) (nreverse (poly-termlist p)))
849 (declaim (ftype (function (poly &optional fixnum) poly) poly-contract))
851 (defun poly-contract (p &optional (k 1))
852 (make-poly-from-termlist (termlist-contract (poly-termlist p) k)
853 (poly-sugar p)))
855 (declaim (ftype (function (poly &optional sequence)) poly-extend))
857 (defun poly-extend (p &optional (m (make-monom 1 :initial-element 0)))
858 (make-poly-from-termlist
859 (termlist-extend (poly-termlist p) m)
860 (+ (poly-sugar p) (monom-sugar m))))
862 (declaim (ftype (function (poly fixnum)) poly-add-variables))
864 (defun poly-add-variables (p k)
865 (setf (poly-termlist p) (termlist-add-variables (poly-termlist p) k))
868 (defun poly-list-add-variables (plist k)
869 (mapcar #'(lambda (p) (poly-add-variables p k)) plist))
871 (defun poly-standard-extension (plist &aux (k (length plist)))
872 "Calculate [U1*P1,U2*P2,...,UK*PK], where PLIST=[P1,P2,...,PK]."
873 (declare (list plist) (fixnum k))
874 (labels ((incf-power (g i)
875 (dolist (x (poly-termlist g))
876 (incf (monom-elt (term-monom x) i)))
877 (incf (poly-sugar g))))
878 (setf plist (poly-list-add-variables plist k))
879 (dotimes (i k plist)
880 (incf-power (nth i plist) i))))
882 (defun saturation-extension (ring f plist &aux (k (length plist)) (d (monom-dimension (poly-lm (car plist)))))
883 "Calculate [F, U1*P1-1,U2*P2-1,...,UK*PK-1], where PLIST=[P1,P2,...,PK]."
884 (setf f (poly-list-add-variables f k)
885 plist (mapcar #'(lambda (x)
886 (setf (poly-termlist x) (nconc (poly-termlist x)
887 (list (make-term (make-monom d :initial-element 0)
888 (funcall (ring-uminus ring) (funcall (ring-unit ring)))))))
890 (poly-standard-extension plist)))
891 (append f plist))
894 (defun polysaturation-extension (ring f plist &aux (k (length plist))
895 (d (+ k (length (poly-lm (car plist))))))
896 "Calculate [F, U1*P1+U2*P2+...+UK*PK-1], where PLIST=[P1,P2,...,PK]."
897 (setf f (poly-list-add-variables f k)
898 plist (apply #'poly-append (poly-standard-extension plist))
899 (cdr (last (poly-termlist plist))) (list (make-term (make-monom d :initial-element 0)
900 (funcall (ring-uminus ring) (funcall (ring-unit ring))))))
901 (append f (list plist)))
903 (defun saturation-extension-1 (ring f p) (polysaturation-extension ring f (list p)))
907 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
909 ;; Evaluation of polynomial (prefix) expressions
911 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
913 (defun coerce-coeff (ring expr vars)
914 "Coerce an element of the coefficient ring to a constant polynomial."
915 ;; Modular arithmetic handler by rat
916 (make-poly-from-termlist (list (make-term (make-monom (length vars) :initial-element 0)
917 (funcall (ring-parse ring) expr)))
920 (defun poly-eval (ring expr vars &optional (list-marker '[))
921 (labels ((p-eval (arg) (poly-eval ring arg vars))
922 (p-eval-list (args) (mapcar #'p-eval args))
923 (p-add (x y) (poly-add ring x y)))
924 (cond
925 ((eql expr 0) (make-poly-zero))
926 ((member expr vars :test #'equalp)
927 (let ((pos (position expr vars :test #'equalp)))
928 (make-variable ring (length vars) pos)))
929 ((atom expr)
930 (coerce-coeff ring expr vars))
931 ((eq (car expr) list-marker)
932 (cons list-marker (p-eval-list (cdr expr))))
934 (case (car expr)
935 (+ (reduce #'p-add (p-eval-list (cdr expr))))
936 (- (case (length expr)
937 (1 (make-poly-zero))
938 (2 (poly-uminus ring (p-eval (cadr expr))))
939 (3 (poly-sub ring (p-eval (cadr expr)) (p-eval (caddr expr))))
940 (otherwise (poly-sub ring (p-eval (cadr expr))
941 (reduce #'p-add (p-eval-list (cddr expr)))))))
943 (if (endp (cddr expr)) ;unary
944 (p-eval (cdr expr))
945 (reduce #'(lambda (p q) (poly-mul ring p q)) (p-eval-list (cdr expr)))))
946 (expt
947 (cond
948 ((member (cadr expr) vars :test #'equalp)
949 ;;Special handling of (expt var pow)
950 (let ((pos (position (cadr expr) vars :test #'equalp)))
951 (make-variable ring (length vars) pos (caddr expr))))
952 ((not (and (integerp (caddr expr)) (plusp (caddr expr))))
953 ;; Negative power means division in coefficient ring
954 ;; Non-integer power means non-polynomial coefficient
955 (coerce-coeff ring expr vars))
956 (t (poly-expt ring (p-eval (cadr expr)) (caddr expr)))))
957 (otherwise
958 (coerce-coeff ring expr vars)))))))
961 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
963 ;; Global optimization/debugging options
965 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
968 ;;All inline functions of this module
969 ;; inlining is disabled on sbcl - sbcl 1.2.7 fails to load if enabled
970 #-sbcl
971 (declaim (inline free-of-vars make-pair-queue pair-queue-insert
972 pair-queue-remove pair-queue-empty-p
973 pair-queue-remove pair-queue-size criterion-1
974 criterion-2 grobner reduced-grobner sugar-pair-key
975 sugar-order normal-form normal-form-step grobner-op spoly
976 equal-test-p
979 ;;Optimization options
980 (declaim (optimize (speed 3) (safety 1)))
983 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
985 ;; Debugging/tracing
987 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
991 (defmacro debug-cgb (&rest args)
992 `(when $poly_grobner_debug (format *terminal-io* ,@args)))
994 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
996 ;; An implementation of Grobner basis
998 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1000 (defun spoly (ring f g)
1001 "It yields the S-polynomial of polynomials F and G."
1002 (declare (type poly f g))
1003 (let* ((lcm (monom-lcm (poly-lm f) (poly-lm g)))
1004 (mf (monom-div lcm (poly-lm f)))
1005 (mg (monom-div lcm (poly-lm g))))
1006 (declare (type monom mf mg))
1007 (multiple-value-bind (c cf cg)
1008 (funcall (ring-ezgcd ring) (poly-lc f) (poly-lc g))
1009 (declare (ignore c))
1010 (poly-sub
1011 ring
1012 (scalar-times-poly ring cg (monom-times-poly mf f))
1013 (scalar-times-poly ring cf (monom-times-poly mg g))))))
1016 (defun poly-primitive-part (ring p)
1017 "Divide polynomial P with integer coefficients by gcd of its
1018 coefficients and return the result."
1019 (declare (type poly p))
1020 (if (poly-zerop p)
1021 (values p 1)
1022 (let ((c (poly-content ring p)))
1023 (values (make-poly-from-termlist (mapcar
1024 #'(lambda (x)
1025 (make-term (term-monom x)
1026 (funcall (ring-div ring) (term-coeff x) c)))
1027 (poly-termlist p))
1028 (poly-sugar p))
1029 c))))
1031 (defun poly-content (ring p)
1032 "Greatest common divisor of the coefficients of the polynomial P. Use the RING structure
1033 to compute the greatest common divisor."
1034 (declare (type poly p))
1035 (reduce (ring-gcd ring) (mapcar #'term-coeff (rest (poly-termlist p))) :initial-value (poly-lc p)))
1038 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1040 ;; An implementation of the division algorithm
1042 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1044 (declaim (ftype (function (ring t t monom poly poly) poly) grobner-op))
1046 (defun grobner-op (ring c1 c2 m f g)
1047 "Returns C2*F-C1*M*G, where F and G are polynomials M is a monomial.
1048 Assume that the leading terms will cancel."
1049 #+grobner-check(funcall (ring-zerop ring)
1050 (funcall (ring-sub ring)
1051 (funcall (ring-mul ring) c2 (poly-lc f))
1052 (funcall (ring-mul ring) c1 (poly-lc g))))
1053 #+grobner-check(monom-equal-p (poly-lm f) (monom-mul m (poly-lm g)))
1054 (poly-sub ring
1055 (scalar-times-poly ring c2 f)
1056 (scalar-times-poly ring c1 (monom-times-poly m g))))
1058 (defun poly-pseudo-divide (ring f fl)
1059 "Pseudo-divide a polynomial F by the list of polynomials FL. Return
1060 multiple values. The first value is a list of quotients A. The second
1061 value is the remainder R. The third argument is a scalar coefficient
1062 C, such that C*F can be divided by FL within the ring of coefficients,
1063 which is not necessarily a field. Finally, the fourth value is an
1064 integer count of the number of reductions performed. The resulting
1065 objects satisfy the equation: C*F= sum A[i]*FL[i] + R."
1066 (declare (type poly f) (list fl))
1067 (do ((r (make-poly-zero))
1068 (c (funcall (ring-unit ring)))
1069 (a (make-list (length fl) :initial-element (make-poly-zero)))
1070 (division-count 0)
1071 (p f))
1072 ((poly-zerop p)
1073 (debug-cgb "~&~3T~d reduction~:p" division-count)
1074 (when (poly-zerop r) (debug-cgb " ---> 0"))
1075 (values (mapcar #'poly-nreverse a) (poly-nreverse r) c division-count))
1076 (declare (fixnum division-count))
1077 (do ((fl fl (rest fl)) ;scan list of divisors
1078 (b a (rest b)))
1079 ((cond
1080 ((endp fl) ;no division occurred
1081 (push (poly-lt p) (poly-termlist r)) ;move lt(p) to remainder
1082 (setf (poly-sugar r) (max (poly-sugar r) (term-sugar (poly-lt p))))
1083 (pop (poly-termlist p)) ;remove lt(p) from p
1085 ((monom-divides-p (poly-lm (car fl)) (poly-lm p)) ;division occurred
1086 (incf division-count)
1087 (multiple-value-bind (gcd c1 c2)
1088 (funcall (ring-ezgcd ring) (poly-lc (car fl)) (poly-lc p))
1089 (declare (ignore gcd))
1090 (let ((m (monom-div (poly-lm p) (poly-lm (car fl)))))
1091 ;; Multiply the equation c*f=sum ai*fi+r+p by c1.
1092 (mapl #'(lambda (x)
1093 (setf (car x) (scalar-times-poly ring c1 (car x))))
1095 (setf r (scalar-times-poly ring c1 r)
1096 c (funcall (ring-mul ring) c c1)
1097 p (grobner-op ring c2 c1 m p (car fl)))
1098 (push (make-term m c2) (poly-termlist (car b))))
1099 t)))))))
1101 (defun poly-exact-divide (ring f g)
1102 "Divide a polynomial F by another polynomial G. Assume that exact division
1103 with no remainder is possible. Returns the quotient."
1104 (declare (type poly f g))
1105 (multiple-value-bind (quot rem coeff division-count)
1106 (poly-pseudo-divide ring f (list g))
1107 (declare (ignore division-count coeff)
1108 (list quot)
1109 (type poly rem)
1110 (type fixnum division-count))
1111 (unless (poly-zerop rem) (error "Exact division failed."))
1112 (car quot)))
1115 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1117 ;; An implementation of the normal form
1119 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1121 (declaim (ftype (function (ring t poly poly t fixnum)
1122 (values poly poly t fixnum))
1123 normal-form-step))
1125 (defun normal-form-step (ring fl p r c division-count
1126 &aux (g (find (poly-lm p) fl
1127 :test #'monom-divisible-by-p
1128 :key #'poly-lm)))
1129 (cond
1130 (g ;division possible
1131 (incf division-count)
1132 (multiple-value-bind (gcd cg cp)
1133 (funcall (ring-ezgcd ring) (poly-lc g) (poly-lc p))
1134 (declare (ignore gcd))
1135 (let ((m (monom-div (poly-lm p) (poly-lm g))))
1136 ;; Multiply the equation c*f=sum ai*fi+r+p by cg.
1137 (setf r (scalar-times-poly ring cg r)
1138 c (funcall (ring-mul ring) c cg)
1139 p (grobner-op ring cp cg m p g))))
1140 (debug-cgb "/"))
1141 (t ;no division possible
1142 (push (poly-lt p) (poly-termlist r)) ;move lt(p) to remainder
1143 (setf (poly-sugar r) (max (poly-sugar r) (term-sugar (poly-lt p))))
1144 (pop (poly-termlist p)) ;remove lt(p) from p
1145 (debug-cgb "+")))
1146 (values p r c division-count))
1148 (declaim (ftype (function (ring poly t &optional t) (values poly t fixnum)) normal-form))
1150 ;; Merge it sometime with poly-pseudo-divide
1151 (defun normal-form (ring f fl &optional (top-reduction-only $poly_top_reduction_only))
1152 ;; Loop invariant: c*f0=sum ai*fi+r+f, where f0 is the initial value of f
1153 #+grobner-check(when (null fl) (warn "normal-form: empty divisor list."))
1154 (do ((r (make-poly-zero))
1155 (c (funcall (ring-unit ring)))
1156 (division-count 0))
1157 ((or (poly-zerop f)
1158 ;;(endp fl)
1159 (and top-reduction-only (not (poly-zerop r))))
1160 (progn
1161 (debug-cgb "~&~3T~d reduction~:p" division-count)
1162 (when (poly-zerop r)
1163 (debug-cgb " ---> 0")))
1164 (setf (poly-termlist f) (nreconc (poly-termlist r) (poly-termlist f)))
1165 (values f c division-count))
1166 (declare (fixnum division-count)
1167 (type poly r))
1168 (multiple-value-setq (f r c division-count)
1169 (normal-form-step ring fl f r c division-count))))
1172 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1174 ;; These are provided mostly for debugging purposes To enable
1175 ;; verification of grobner bases with BUCHBERGER-CRITERION, do
1176 ;; (pushnew :grobner-check *features*) and compile/load this file.
1177 ;; With this feature, the calculations will slow down CONSIDERABLY.
1179 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1181 (defun buchberger-criterion (ring g)
1182 "Returns T if G is a Grobner basis, by using the Buchberger
1183 criterion: for every two polynomials h1 and h2 in G the S-polynomial
1184 S(h1,h2) reduces to 0 modulo G."
1185 (every
1186 #'poly-zerop
1187 (grobner-makelist (normal-form ring (spoly ring (elt g i) (elt g j)) g nil)
1188 (i 0 (- (length g) 2))
1189 (j (1+ i) (1- (length g))))))
1191 (defun grobner-test (ring g f)
1192 "Test whether G is a Grobner basis and F is contained in G. Return T
1193 upon success and NIL otherwise."
1194 (debug-cgb "~&GROBNER CHECK: ")
1195 (let (($poly_grobner_debug nil)
1196 (stat1 (buchberger-criterion ring g))
1197 (stat2
1198 (every #'poly-zerop
1199 (grobner-makelist (normal-form ring (copy-tree (elt f i)) g nil)
1200 (i 0 (1- (length f)))))))
1201 (unless stat1 (error "~&Buchberger criterion failed."))
1202 (unless stat2
1203 (error "~&Original polys not in ideal spanned by Grobner.")))
1204 (debug-cgb "~&GROBNER CHECK END")
1208 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1210 ;; Pair queue implementation
1212 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1214 (defun sugar-pair-key (p q &aux (lcm (monom-lcm (poly-lm p) (poly-lm q)))
1215 (d (monom-sugar lcm)))
1216 "Returns list (S LCM-TOTAL-DEGREE) where S is the sugar of the S-polynomial of
1217 polynomials P and Q, and LCM-TOTAL-DEGREE is the degree of is LCM(LM(P),LM(Q))."
1218 (declare (type poly p q) (type monom lcm) (type fixnum d))
1219 (cons (max
1220 (+ (- d (monom-sugar (poly-lm p))) (poly-sugar p))
1221 (+ (- d (monom-sugar (poly-lm q))) (poly-sugar q)))
1222 lcm))
1224 (defstruct (pair
1225 (:constructor make-pair (first second
1226 &aux
1227 (sugar (car (sugar-pair-key first second)))
1228 (division-data nil))))
1229 (first nil :type poly)
1230 (second nil :type poly)
1231 (sugar 0 :type fixnum)
1232 (division-data nil :type list))
1234 ;;(defun pair-sugar (pair &aux (p (pair-first pair)) (q (pair-second pair)))
1235 ;; (car (sugar-pair-key p q)))
1237 (defun sugar-order (x y)
1238 "Pair order based on sugar, ties broken by normal strategy."
1239 (declare (type cons x y))
1240 (or (< (car x) (car y))
1241 (and (= (car x) (car y))
1242 (< (monom-total-degree (cdr x))
1243 (monom-total-degree (cdr y))))))
1245 (defvar *pair-key-function* #'sugar-pair-key
1246 "Function that, given two polynomials as argument, computed the key
1247 in the pair queue.")
1249 (defvar *pair-order* #'sugar-order
1250 "Function that orders the keys of pairs.")
1252 (defun make-pair-queue ()
1253 "Constructs a priority queue for critical pairs."
1254 (make-priority-queue
1255 :element-type 'pair
1256 :element-key #'(lambda (pair) (funcall *pair-key-function* (pair-first pair) (pair-second pair)))
1257 :test *pair-order*))
1259 (defun pair-queue-initialize (pq f start
1260 &aux
1261 (s (1- (length f)))
1262 (b (nconc (grobner-makelist (make-pair (elt f i) (elt f j))
1263 (i 0 (1- start)) (j start s))
1264 (grobner-makelist (make-pair (elt f i) (elt f j))
1265 (i start (1- s)) (j (1+ i) s)))))
1266 "Initializes the priority for critical pairs. F is the initial list of polynomials.
1267 START is the first position beyond the elements which form a partial
1268 grobner basis, i.e. satisfy the Buchberger criterion."
1269 (declare (type priority-queue pq) (type fixnum start))
1270 (dolist (pair b pq)
1271 (priority-queue-insert pq pair)))
1273 (defun pair-queue-insert (b pair)
1274 (priority-queue-insert b pair))
1276 (defun pair-queue-remove (b)
1277 (priority-queue-remove b))
1279 (defun pair-queue-size (b)
1280 (priority-queue-size b))
1282 (defun pair-queue-empty-p (b)
1283 (priority-queue-empty-p b))
1285 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1287 ;; Buchberger Algorithm Implementation
1289 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1291 (defun buchberger (ring f start &optional (top-reduction-only $poly_top_reduction_only))
1292 "An implementation of the Buchberger algorithm. Return Grobner basis
1293 of the ideal generated by the polynomial list F. Polynomials 0 to
1294 START-1 are assumed to be a Grobner basis already, so that certain
1295 critical pairs will not be examined. If TOP-REDUCTION-ONLY set, top
1296 reduction will be performed. This function assumes that all polynomials
1297 in F are non-zero."
1298 (declare (type fixnum start))
1299 (when (endp f) (return-from buchberger f)) ;cut startup costs
1300 (debug-cgb "~&GROBNER BASIS - BUCHBERGER ALGORITHM")
1301 (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
1302 #+grobner-check (when (plusp start)
1303 (grobner-test ring (subseq f 0 start) (subseq f 0 start)))
1304 ;;Initialize critical pairs
1305 (let ((b (pair-queue-initialize (make-pair-queue)
1306 f start))
1307 (b-done (make-hash-table :test #'equal)))
1308 (declare (type priority-queue b) (type hash-table b-done))
1309 (dotimes (i (1- start))
1310 (do ((j (1+ i) (1+ j))) ((>= j start))
1311 (setf (gethash (list (elt f i) (elt f j)) b-done) t)))
1312 (do ()
1313 ((pair-queue-empty-p b)
1314 #+grobner-check(grobner-test ring f f)
1315 (debug-cgb "~&GROBNER END")
1317 (let ((pair (pair-queue-remove b)))
1318 (declare (type pair pair))
1319 (cond
1320 ((criterion-1 pair) nil)
1321 ((criterion-2 pair b-done f) nil)
1323 (let ((sp (normal-form ring (spoly ring (pair-first pair)
1324 (pair-second pair))
1325 f top-reduction-only)))
1326 (declare (type poly sp))
1327 (cond
1328 ((poly-zerop sp)
1329 nil)
1331 (setf sp (poly-primitive-part ring sp)
1332 f (nconc f (list sp)))
1333 ;; Add new critical pairs
1334 (dolist (h f)
1335 (pair-queue-insert b (make-pair h sp)))
1336 (debug-cgb "~&Sugar: ~d Polynomials: ~d; Pairs left: ~d; Pairs done: ~d;"
1337 (pair-sugar pair) (length f) (pair-queue-size b)
1338 (hash-table-count b-done)))))))
1339 (setf (gethash (list (pair-first pair) (pair-second pair)) b-done)
1340 t)))))
1342 (defun parallel-buchberger (ring f start &optional (top-reduction-only $poly_top_reduction_only))
1343 "An implementation of the Buchberger algorithm. Return Grobner basis
1344 of the ideal generated by the polynomial list F. Polynomials 0 to
1345 START-1 are assumed to be a Grobner basis already, so that certain
1346 critical pairs will not be examined. If TOP-REDUCTION-ONLY set, top
1347 reduction will be performed."
1348 (declare (ignore top-reduction-only)
1349 (type fixnum start))
1350 (when (endp f) (return-from parallel-buchberger f)) ;cut startup costs
1351 (debug-cgb "~&GROBNER BASIS - PARALLEL-BUCHBERGER ALGORITHM")
1352 (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
1353 #+grobner-check (when (plusp start)
1354 (grobner-test ring (subseq f 0 start) (subseq f 0 start)))
1355 ;;Initialize critical pairs
1356 (let ((b (pair-queue-initialize (make-pair-queue) f start))
1357 (b-done (make-hash-table :test #'equal)))
1358 (declare (type priority-queue b)
1359 (type hash-table b-done))
1360 (dotimes (i (1- start))
1361 (do ((j (1+ i) (1+ j))) ((>= j start))
1362 (declare (type fixnum j))
1363 (setf (gethash (list (elt f i) (elt f j)) b-done) t)))
1364 (do ()
1365 ((pair-queue-empty-p b)
1366 #+grobner-check(grobner-test ring f f)
1367 (debug-cgb "~&GROBNER END")
1369 (let ((pair (pair-queue-remove b)))
1370 (when (null (pair-division-data pair))
1371 (setf (pair-division-data pair) (list (spoly ring
1372 (pair-first pair)
1373 (pair-second pair))
1374 (make-poly-zero)
1375 (funcall (ring-unit ring))
1376 0)))
1377 (cond
1378 ((criterion-1 pair) nil)
1379 ((criterion-2 pair b-done f) nil)
1381 (let* ((dd (pair-division-data pair))
1382 (p (first dd))
1383 (sp (second dd))
1384 (c (third dd))
1385 (division-count (fourth dd)))
1386 (cond
1387 ((poly-zerop p) ;normal form completed
1388 (debug-cgb "~&~3T~d reduction~:p" division-count)
1389 (cond
1390 ((poly-zerop sp)
1391 (debug-cgb " ---> 0")
1392 nil)
1394 (setf sp (poly-nreverse sp)
1395 sp (poly-primitive-part ring sp)
1396 f (nconc f (list sp)))
1397 ;; Add new critical pairs
1398 (dolist (h f)
1399 (pair-queue-insert b (make-pair h sp)))
1400 (debug-cgb "~&Sugar: ~d Polynomials: ~d; Pairs left: ~d; Pairs done: ~d;"
1401 (pair-sugar pair) (length f) (pair-queue-size b)
1402 (hash-table-count b-done))))
1403 (setf (gethash (list (pair-first pair) (pair-second pair))
1404 b-done) t))
1405 (t ;normal form not complete
1406 (do ()
1407 ((cond
1408 ((> (poly-sugar sp) (pair-sugar pair))
1409 (debug-cgb "(~a)?" (poly-sugar sp))
1411 ((poly-zerop p)
1412 (debug-cgb ".")
1414 (t nil))
1415 (setf (first dd) p
1416 (second dd) sp
1417 (third dd) c
1418 (fourth dd) division-count
1419 (pair-sugar pair) (poly-sugar sp))
1420 (pair-queue-insert b pair))
1421 (multiple-value-setq (p sp c division-count)
1422 (normal-form-step ring f p sp c division-count))))))))))))
1424 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1426 ;; Grobner Criteria
1428 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1430 (defun criterion-1 (pair)
1431 "Returns T if the leading monomials of the two polynomials
1432 in G pointed to by the integers in PAIR have disjoint (relatively prime)
1433 monomials. This test is known as the first Buchberger criterion."
1434 (declare (type pair pair))
1435 (let ((f (pair-first pair))
1436 (g (pair-second pair)))
1437 (when (monom-rel-prime-p (poly-lm f) (poly-lm g))
1438 (debug-cgb ":1")
1439 (return-from criterion-1 t))))
1441 (defun criterion-2 (pair b-done partial-basis
1442 &aux (f (pair-first pair)) (g (pair-second pair))
1443 (place :before))
1444 "Returns T if the leading monomial of some element P of
1445 PARTIAL-BASIS divides the LCM of the leading monomials of the two
1446 polynomials in the polynomial list PARTIAL-BASIS, and P paired with
1447 each of the polynomials pointed to by the the PAIR has already been
1448 treated, as indicated by the absence in the hash table B-done."
1449 (declare (type pair pair) (type hash-table b-done)
1450 (type poly f g))
1451 ;; In the code below we assume that pairs are ordered as follows:
1452 ;; if PAIR is (I J) then I appears before J in the PARTIAL-BASIS.
1453 ;; We traverse the list PARTIAL-BASIS and keep track of where we
1454 ;; are, so that we can produce the pairs in the correct order
1455 ;; when we check whether they have been processed, i.e they
1456 ;; appear in the hash table B-done
1457 (dolist (h partial-basis nil)
1458 (cond
1459 ((eq h f)
1460 #+grobner-check(assert (eq place :before))
1461 (setf place :in-the-middle))
1462 ((eq h g)
1463 #+grobner-check(assert (eq place :in-the-middle))
1464 (setf place :after))
1465 ((and (monom-divides-monom-lcm-p (poly-lm h) (poly-lm f) (poly-lm g))
1466 (gethash (case place
1467 (:before (list h f))
1468 ((:in-the-middle :after) (list f h)))
1469 b-done)
1470 (gethash (case place
1471 ((:before :in-the-middle) (list h g))
1472 (:after (list g h)))
1473 b-done))
1474 (debug-cgb ":2")
1475 (return-from criterion-2 t)))))
1478 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1480 ;; An implementation of the algorithm of Gebauer and Moeller, as
1481 ;; described in the book of Becker-Weispfenning, p. 232
1483 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1485 (defun gebauer-moeller (ring f start &optional (top-reduction-only $poly_top_reduction_only))
1486 "Compute Grobner basis by using the algorithm of Gebauer and
1487 Moeller. This algorithm is described as BUCHBERGERNEW2 in the book by
1488 Becker-Weispfenning entitled ``Grobner Bases''. This function assumes
1489 that all polynomials in F are non-zero."
1490 (declare (ignore top-reduction-only)
1491 (type fixnum start))
1492 (cond
1493 ((endp f) (return-from gebauer-moeller nil))
1494 ((endp (cdr f))
1495 (return-from gebauer-moeller (list (poly-primitive-part ring (car f))))))
1496 (debug-cgb "~&GROBNER BASIS - GEBAUER MOELLER ALGORITHM")
1497 (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
1498 #+grobner-check (when (plusp start)
1499 (grobner-test ring (subseq f 0 start) (subseq f 0 start)))
1500 (let ((b (make-pair-queue))
1501 (g (subseq f 0 start))
1502 (f1 (subseq f start)))
1503 (do () ((endp f1))
1504 (multiple-value-setq (g b)
1505 (gebauer-moeller-update g b (poly-primitive-part ring (pop f1)))))
1506 (do () ((pair-queue-empty-p b))
1507 (let* ((pair (pair-queue-remove b))
1508 (g1 (pair-first pair))
1509 (g2 (pair-second pair))
1510 (h (normal-form ring (spoly ring g1 g2)
1512 nil #| Always fully reduce! |#
1514 (unless (poly-zerop h)
1515 (setf h (poly-primitive-part ring h))
1516 (multiple-value-setq (g b)
1517 (gebauer-moeller-update g b h))
1518 (debug-cgb "~&Sugar: ~d Polynomials: ~d; Pairs left: ~d~%"
1519 (pair-sugar pair) (length g) (pair-queue-size b))
1521 #+grobner-check(grobner-test ring g f)
1522 (debug-cgb "~&GROBNER END")
1525 (defun gebauer-moeller-update (g b h
1526 &aux
1527 c d e
1528 (b-new (make-pair-queue))
1529 g-new)
1530 "An implementation of the auxiliary UPDATE algorithm used by the
1531 Gebauer-Moeller algorithm. G is a list of polynomials, B is a list of
1532 critical pairs and H is a new polynomial which possibly will be added
1533 to G. The naming conventions used are very close to the one used in
1534 the book of Becker-Weispfenning."
1535 (declare
1536 #+allegro (dynamic-extent b)
1537 (type poly h)
1538 (type priority-queue b))
1539 (setf c g d nil)
1540 (do () ((endp c))
1541 (let ((g1 (pop c)))
1542 (declare (type poly g1))
1543 (when (or (monom-rel-prime-p (poly-lm h) (poly-lm g1))
1544 (and
1545 (notany #'(lambda (g2) (monom-lcm-divides-monom-lcm-p
1546 (poly-lm h) (poly-lm g2)
1547 (poly-lm h) (poly-lm g1)))
1549 (notany #'(lambda (g2) (monom-lcm-divides-monom-lcm-p
1550 (poly-lm h) (poly-lm g2)
1551 (poly-lm h) (poly-lm g1)))
1552 d)))
1553 (push g1 d))))
1554 (setf e nil)
1555 (do () ((endp d))
1556 (let ((g1 (pop d)))
1557 (declare (type poly g1))
1558 (unless (monom-rel-prime-p (poly-lm h) (poly-lm g1))
1559 (push g1 e))))
1560 (do () ((pair-queue-empty-p b))
1561 (let* ((pair (pair-queue-remove b))
1562 (g1 (pair-first pair))
1563 (g2 (pair-second pair)))
1564 (declare (type pair pair)
1565 (type poly g1 g2))
1566 (when (or (not (monom-divides-monom-lcm-p
1567 (poly-lm h)
1568 (poly-lm g1) (poly-lm g2)))
1569 (monom-lcm-equal-monom-lcm-p
1570 (poly-lm g1) (poly-lm h)
1571 (poly-lm g1) (poly-lm g2))
1572 (monom-lcm-equal-monom-lcm-p
1573 (poly-lm h) (poly-lm g2)
1574 (poly-lm g1) (poly-lm g2)))
1575 (pair-queue-insert b-new (make-pair g1 g2)))))
1576 (dolist (g3 e)
1577 (pair-queue-insert b-new (make-pair h g3)))
1578 (setf g-new nil)
1579 (do () ((endp g))
1580 (let ((g1 (pop g)))
1581 (declare (type poly g1))
1582 (unless (monom-divides-p (poly-lm h) (poly-lm g1))
1583 (push g1 g-new))))
1584 (push h g-new)
1585 (values g-new b-new))
1588 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1590 ;; Standard postprocessing of Grobner bases
1592 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1594 (defun reduction (ring plist)
1595 "Reduce a list of polynomials PLIST, so that non of the terms in any of
1596 the polynomials is divisible by a leading monomial of another
1597 polynomial. Return the reduced list."
1598 (do ((q plist)
1599 (found t))
1600 ((not found)
1601 (mapcar #'(lambda (x) (poly-primitive-part ring x)) q))
1602 ;;Find p in Q such that p is reducible mod Q\{p}
1603 (setf found nil)
1604 (dolist (x q)
1605 (let ((q1 (remove x q)))
1606 (multiple-value-bind (h c div-count)
1607 (normal-form ring x q1 nil #| not a top reduction! |# )
1608 (declare (ignore c))
1609 (unless (zerop div-count)
1610 (setf found t q q1)
1611 (unless (poly-zerop h)
1612 (setf q (nconc q1 (list h))))
1613 (return)))))))
1615 (defun minimization (p)
1616 "Returns a sublist of the polynomial list P spanning the same
1617 monomial ideal as P but minimal, i.e. no leading monomial
1618 of a polynomial in the sublist divides the leading monomial
1619 of another polynomial."
1620 (do ((q p)
1621 (found t))
1622 ((not found) q)
1623 ;;Find p in Q such that lm(p) is in LM(Q\{p})
1624 (setf found nil
1625 q (dolist (x q q)
1626 (let ((q1 (remove x q)))
1627 (when (member-if #'(lambda (p) (monom-divides-p (poly-lm x) (poly-lm p))) q1)
1628 (setf found t)
1629 (return q1)))))))
1631 (defun poly-normalize (ring p &aux (c (poly-lc p)))
1632 "Divide a polynomial by its leading coefficient. It assumes
1633 that the division is possible, which may not always be the
1634 case in rings which are not fields. The exact division operator
1635 is assumed to be provided by the RING structure of the
1636 COEFFICIENT-RING package."
1637 (mapc #'(lambda (term)
1638 (setf (term-coeff term) (funcall (ring-div ring) (term-coeff term) c)))
1639 (poly-termlist p))
1642 (defun poly-normalize-list (ring plist)
1643 "Divide every polynomial in a list PLIST by its leading coefficient. "
1644 (mapcar #'(lambda (x) (poly-normalize ring x)) plist))
1647 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1649 ;; Algorithm and Pair heuristic selection
1651 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1653 (defun find-grobner-function (algorithm)
1654 "Return a function which calculates Grobner basis, based on its
1655 names. Names currently used are either Lisp symbols, Maxima symbols or
1656 keywords."
1657 (ecase algorithm
1658 ((buchberger :buchberger $buchberger) #'buchberger)
1659 ((parallel-buchberger :parallel-buchberger $parallel_buchberger) #'parallel-buchberger)
1660 ((gebauer-moeller :gebauer_moeller $gebauer_moeller) #'gebauer-moeller)))
1662 (defun grobner (ring f &optional (start 0) (top-reduction-only nil))
1663 ;;(setf F (sort F #'< :key #'sugar))
1664 (funcall
1665 (find-grobner-function $poly_grobner_algorithm)
1666 ring f start top-reduction-only))
1668 (defun reduced-grobner (ring f &optional (start 0) (top-reduction-only $poly_top_reduction_only))
1669 (reduction ring (grobner ring f start top-reduction-only)))
1671 (defun set-pair-heuristic (method)
1672 "Sets up variables *PAIR-KEY-FUNCTION* and *PAIR-ORDER* used
1673 to determine the priority of critical pairs in the priority queue."
1674 (ecase method
1675 ((sugar :sugar $sugar)
1676 (setf *pair-key-function* #'sugar-pair-key
1677 *pair-order* #'sugar-order))
1678 ; ((minimal-mock-spoly :minimal-mock-spoly $minimal_mock_spoly)
1679 ; (setf *pair-key-function* #'mock-spoly
1680 ; *pair-order* #'mock-spoly-order))
1681 ((minimal-lcm :minimal-lcm $minimal_lcm)
1682 (setf *pair-key-function* #'(lambda (p q)
1683 (monom-lcm (poly-lm p) (poly-lm q)))
1684 *pair-order* #'reverse-monomial-order))
1685 ((minimal-total-degree :minimal-total-degree $minimal_total_degree)
1686 (setf *pair-key-function* #'(lambda (p q)
1687 (monom-total-degree
1688 (monom-lcm (poly-lm p) (poly-lm q))))
1689 *pair-order* #'<))
1690 ((minimal-length :minimal-length $minimal_length)
1691 (setf *pair-key-function* #'(lambda (p q)
1692 (+ (poly-length p) (poly-length q)))
1693 *pair-order* #'<))))
1696 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1698 ;; Operations in ideal theory
1700 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1702 ;; Does the term depend on variable K?
1703 (defun term-depends-p (term k)
1704 "Return T if the term TERM depends on variable number K."
1705 (monom-depends-p (term-monom term) k))
1707 ;; Does the polynomial P depend on variable K?
1708 (defun poly-depends-p (p k)
1709 "Return T if the term polynomial P depends on variable number K."
1710 (some #'(lambda (term) (term-depends-p term k)) (poly-termlist p)))
1712 (defun ring-intersection (plist k)
1713 "This function assumes that polynomial list PLIST is a Grobner basis
1714 and it calculates the intersection with the ring R[x[k+1],...,x[n]], i.e.
1715 it discards polynomials which depend on variables x[0], x[1], ..., x[k]."
1716 (dotimes (i k plist)
1717 (setf plist
1718 (remove-if #'(lambda (p)
1719 (poly-depends-p p i))
1720 plist))))
1722 (defun elimination-ideal (ring flist k
1723 &optional (top-reduction-only $poly_top_reduction_only) (start 0)
1724 &aux (*monomial-order*
1725 (or *elimination-order*
1726 (elimination-order k))))
1727 (ring-intersection (reduced-grobner ring flist start top-reduction-only) k))
1729 (defun colon-ideal (ring f g &optional (top-reduction-only $poly_top_reduction_only))
1730 "Returns the reduced Grobner basis of the colon ideal Id(F):Id(G),
1731 where F and G are two lists of polynomials. The colon ideal I:J is
1732 defined as the set of polynomials H such that for all polynomials W in
1733 J the polynomial W*H belongs to I."
1734 (cond
1735 ((endp g)
1736 ;;Id(G) consists of 0 only so W*0=0 belongs to Id(F)
1737 (if (every #'poly-zerop f)
1738 (error "First ideal must be non-zero.")
1739 (list (make-poly
1740 (list (make-term
1741 (make-monom (monom-dimension (poly-lm (find-if-not #'poly-zerop f)))
1742 :initial-element 0)
1743 (funcall (ring-unit ring))))))))
1744 ((endp (cdr g))
1745 (colon-ideal-1 ring f (car g) top-reduction-only))
1747 (ideal-intersection ring
1748 (colon-ideal-1 ring f (car g) top-reduction-only)
1749 (colon-ideal ring f (rest g) top-reduction-only)
1750 top-reduction-only))))
1752 (defun colon-ideal-1 (ring f g &optional (top-reduction-only $poly_top_reduction_only))
1753 "Returns the reduced Grobner basis of the colon ideal Id(F):Id({G}), where
1754 F is a list of polynomials and G is a polynomial."
1755 (mapcar #'(lambda (x) (poly-exact-divide ring x g)) (ideal-intersection ring f (list g) top-reduction-only)))
1758 (defun ideal-intersection (ring f g &optional (top-reduction-only $poly_top_reduction_only)
1759 &aux (*monomial-order* (or *elimination-order*
1760 #'elimination-order-1)))
1761 (mapcar #'poly-contract
1762 (ring-intersection
1763 (reduced-grobner
1764 ring
1765 (append (mapcar #'(lambda (p) (poly-extend p (make-monom 1 :initial-element 1))) f)
1766 (mapcar #'(lambda (p)
1767 (poly-append (poly-extend (poly-uminus ring p)
1768 (make-monom 1 :initial-element 1))
1769 (poly-extend p)))
1772 top-reduction-only)
1773 1)))
1775 (defun poly-lcm (ring f g)
1776 "Return LCM (least common multiple) of two polynomials F and G.
1777 The polynomials must be ordered according to monomial order PRED
1778 and their coefficients must be compatible with the RING structure
1779 defined in the COEFFICIENT-RING package."
1780 (cond
1781 ((poly-zerop f) f)
1782 ((poly-zerop g) g)
1783 ((and (endp (cdr (poly-termlist f))) (endp (cdr (poly-termlist g))))
1784 (let ((m (monom-lcm (poly-lm f) (poly-lm g))))
1785 (make-poly-from-termlist (list (make-term m (funcall (ring-lcm ring) (poly-lc f) (poly-lc g)))))))
1787 (multiple-value-bind (f f-cont)
1788 (poly-primitive-part ring f)
1789 (multiple-value-bind (g g-cont)
1790 (poly-primitive-part ring g)
1791 (scalar-times-poly
1792 ring
1793 (funcall (ring-lcm ring) f-cont g-cont)
1794 (poly-primitive-part ring (car (ideal-intersection ring (list f) (list g) nil)))))))))
1796 ;; Do two Grobner bases yield the same ideal?
1797 (defun grobner-equal (ring g1 g2)
1798 "Returns T if two lists of polynomials G1 and G2, assumed to be Grobner bases,
1799 generate the same ideal, and NIL otherwise."
1800 (and (grobner-subsetp ring g1 g2) (grobner-subsetp ring g2 g1)))
1802 (defun grobner-subsetp (ring g1 g2)
1803 "Returns T if a list of polynomials G1 generates
1804 an ideal contained in the ideal generated by a polynomial list G2,
1805 both G1 and G2 assumed to be Grobner bases. Returns NIL otherwise."
1806 (every #'(lambda (p) (grobner-member ring p g2)) g1))
1808 (defun grobner-member (ring p g)
1809 "Returns T if a polynomial P belongs to the ideal generated by the
1810 polynomial list G, which is assumed to be a Grobner basis. Returns NIL otherwise."
1811 (poly-zerop (normal-form ring p g nil)))
1813 ;; Calculate F : p^inf
1814 (defun ideal-saturation-1 (ring f p start &optional (top-reduction-only $poly_top_reduction_only)
1815 &aux (*monomial-order* (or *elimination-order*
1816 #'elimination-order-1)))
1817 "Returns the reduced Grobner basis of the saturation of the ideal
1818 generated by a polynomial list F in the ideal generated by a single
1819 polynomial P. The saturation ideal is defined as the set of
1820 polynomials H such for some natural number n (* (EXPT P N) H) is in the ideal
1821 F. Geometrically, over an algebraically closed field, this is the set
1822 of polynomials in the ideal generated by F which do not identically
1823 vanish on the variety of P."
1824 (mapcar
1825 #'poly-contract
1826 (ring-intersection
1827 (reduced-grobner
1828 ring
1829 (saturation-extension-1 ring f p)
1830 start top-reduction-only)
1831 1)))
1835 ;; Calculate F : p1^inf : p2^inf : ... : ps^inf
1836 (defun ideal-polysaturation-1 (ring f plist start &optional (top-reduction-only $poly_top_reduction_only))
1837 "Returns the reduced Grobner basis of the ideal obtained by a
1838 sequence of successive saturations in the polynomials
1839 of the polynomial list PLIST of the ideal generated by the
1840 polynomial list F."
1841 (cond
1842 ((endp plist) (reduced-grobner ring f start top-reduction-only))
1843 (t (let ((g (ideal-saturation-1 ring f (car plist) start top-reduction-only)))
1844 (ideal-polysaturation-1 ring g (rest plist) (length g) top-reduction-only)))))
1846 (defun ideal-saturation (ring f g start &optional (top-reduction-only $poly_top_reduction_only)
1847 &aux
1848 (k (length g))
1849 (*monomial-order* (or *elimination-order*
1850 (elimination-order k))))
1851 "Returns the reduced Grobner basis of the saturation of the ideal
1852 generated by a polynomial list F in the ideal generated a polynomial
1853 list G. The saturation ideal is defined as the set of polynomials H
1854 such for some natural number n and some P in the ideal generated by G
1855 the polynomial P**N * H is in the ideal spanned by F. Geometrically,
1856 over an algebraically closed field, this is the set of polynomials in
1857 the ideal generated by F which do not identically vanish on the
1858 variety of G."
1859 (mapcar
1860 #'(lambda (q) (poly-contract q k))
1861 (ring-intersection
1862 (reduced-grobner ring
1863 (polysaturation-extension ring f g)
1864 start
1865 top-reduction-only)
1866 k)))
1868 (defun ideal-polysaturation (ring f ideal-list start &optional (top-reduction-only $poly_top_reduction_only))
1869 "Returns the reduced Grobner basis of the ideal obtained by a
1870 successive applications of IDEAL-SATURATION to F and lists of
1871 polynomials in the list IDEAL-LIST."
1872 (cond
1873 ((endp ideal-list) f)
1874 (t (let ((h (ideal-saturation ring f (car ideal-list) start top-reduction-only)))
1875 (ideal-polysaturation ring h (rest ideal-list) (length h) top-reduction-only)))))
1878 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1880 ;; Set up the coefficients to be polynomials
1882 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1884 ;; (defun poly-ring (ring vars)
1885 ;; (make-ring
1886 ;; :parse #'(lambda (expr) (poly-eval ring expr vars))
1887 ;; :unit #'(lambda () (poly-unit ring (length vars)))
1888 ;; :zerop #'poly-zerop
1889 ;; :add #'(lambda (x y) (poly-add ring x y))
1890 ;; :sub #'(lambda (x y) (poly-sub ring x y))
1891 ;; :uminus #'(lambda (x) (poly-uminus ring x))
1892 ;; :mul #'(lambda (x y) (poly-mul ring x y))
1893 ;; :div #'(lambda (x y) (poly-exact-divide ring x y))
1894 ;; :lcm #'(lambda (x y) (poly-lcm ring x y))
1895 ;; :ezgcd #'(lambda (x y &aux (gcd (poly-gcd ring x y)))
1896 ;; (values gcd
1897 ;; (poly-exact-divide ring x gcd)
1898 ;; (poly-exact-divide ring y gcd)))
1899 ;; :gcd #'(lambda (x y) (poly-gcd x y))))
1902 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1904 ;; Conversion from internal to infix form
1906 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1908 (defun coerce-to-infix (poly-type object vars)
1909 (case poly-type
1910 (:termlist
1911 `(+ ,@(mapcar #'(lambda (term) (coerce-to-infix :term term vars)) object)))
1912 (:polynomial
1913 (coerce-to-infix :termlist (poly-termlist object) vars))
1914 (:poly-list
1915 `([ ,@(mapcar #'(lambda (p) (coerce-to-infix :polynomial p vars)) object)))
1916 (:term
1917 `(* ,(term-coeff object)
1918 ,@(mapcar #'(lambda (var power) `(expt ,var ,power))
1919 vars (monom-exponents (term-monom object)))))
1920 (otherwise
1921 object)))
1924 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1926 ;; Maxima expression ring
1928 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1930 (defparameter *expression-ring*
1931 (make-ring
1932 ;;(defun coeff-zerop (expr) (meval1 `(($is) (($equal) ,expr 0))))
1933 :parse #'(lambda (expr)
1934 (when modulus (setf expr ($rat expr)))
1935 expr)
1936 :unit #'(lambda () (if modulus ($rat 1) 1))
1937 :zerop #'(lambda (expr)
1938 ;;When is exactly a maxima expression equal to 0?
1939 (cond ((numberp expr)
1940 (= expr 0))
1941 ((atom expr) nil)
1943 (case (caar expr)
1944 (mrat (eql ($ratdisrep expr) 0))
1945 (otherwise (eql (sratsimp expr) 0))))))
1946 :add #'(lambda (x y) (sratsimp (m+ x y)))
1947 :sub #'(lambda (x y) (sratsimp (m- x y)))
1948 :uminus #'(lambda (x) (m- x))
1949 :mul #'(lambda (x y) (m* x y))
1950 ;;(defun coeff-div (x y) (cadr ($divide x y)))
1951 :div #'(lambda (x y) (sratsimp (m// x y)))
1952 :lcm #'(lambda (x y) (sratsimp (m// (m* x y) (second ($ezgcd x y)))))
1953 :ezgcd #'(lambda (x y) (apply #'values (cdr ($ezgcd x y))))
1954 :gcd #'(lambda (x y) (second ($ezgcd x y)))))
1956 (defvar *maxima-ring* *expression-ring*
1957 "The ring of coefficients, over which all polynomials
1958 are assumed to be defined.")
1961 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1963 ;; Maxima expression parsing
1965 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1967 (defun equal-test-p (expr1 expr2)
1968 (alike1 expr1 expr2))
1970 (defun coerce-maxima-list (expr)
1971 "convert a maxima list to lisp list."
1972 (cond
1973 ((and (consp (car expr)) (eql (caar expr) 'mlist)) (cdr expr))
1974 (t expr)))
1976 (defun free-of-vars (expr vars) (apply #'$freeof `(,@vars ,expr)))
1978 ;; This function removes rational numbers from coefficients of polynomials.
1979 (defun parse-poly (expr vars)
1980 (parse-poly1 ($num (sratsimp expr)) vars))
1982 (defun parse-poly1 (expr vars &aux (vars (coerce-maxima-list vars)))
1983 "Convert a maxima polynomial expression EXPR in variables VARS to internal form."
1984 (labels ((parse (arg) (parse-poly1 arg vars))
1985 (parse-list (args) (mapcar #'parse args)))
1986 (cond
1987 ((eql expr 0) (make-poly-zero))
1988 ((member expr vars :test #'equal-test-p)
1989 (let ((pos (position expr vars :test #'equal-test-p)))
1990 (make-variable *maxima-ring* (length vars) pos)))
1991 ((free-of-vars expr vars)
1992 ;;This means that variable-free CRE and Poisson forms will be converted
1993 ;;to coefficients intact
1994 (coerce-coeff *maxima-ring* expr vars))
1996 (case (caar expr)
1997 (mplus (reduce #'(lambda (x y) (poly-add *maxima-ring* x y)) (parse-list (cdr expr))))
1998 (mminus (poly-uminus *maxima-ring* (parse (cadr expr))))
1999 (mtimes
2000 (if (endp (cddr expr)) ;unary
2001 (parse (cdr expr))
2002 (reduce #'(lambda (p q) (poly-mul *maxima-ring* p q)) (parse-list (cdr expr)))))
2003 (mexpt
2004 (cond
2005 ((member (cadr expr) vars :test #'equal-test-p)
2006 ;;Special handling of (expt var pow)
2007 (let ((pos (position (cadr expr) vars :test #'equal-test-p)))
2008 (make-variable *maxima-ring* (length vars) pos (caddr expr))))
2009 ((not (and (integerp (caddr expr)) (plusp (caddr expr))))
2010 ;; Negative power means division in coefficient ring
2011 ;; Non-integer power means non-polynomial coefficient
2012 (mtell "~%Warning: Expression ~%~M~%contains power which is not a positive integer. Parsing as coefficient.~%"
2013 expr)
2014 (coerce-coeff *maxima-ring* expr vars))
2015 (t (poly-expt *maxima-ring* (parse (cadr expr)) (caddr expr)))))
2016 (mrat (parse ($ratdisrep expr)))
2017 (mpois (parse ($outofpois expr)))
2018 (otherwise
2019 (coerce-coeff *maxima-ring* expr vars)))))))
2021 (defun parse-poly-list (expr vars)
2022 (case (caar expr)
2023 (mlist (mapcar #'(lambda (p) (parse-poly p vars)) (cdr expr)))
2024 (t (merror "Expression ~M is not a list of polynomials in variables ~M."
2025 expr vars))))
2026 (defun parse-poly-list-list (poly-list-list vars)
2027 (mapcar #'(lambda (g) (parse-poly-list g vars)) (coerce-maxima-list poly-list-list)))
2030 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2032 ;; Order utilities
2034 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2035 (defun find-order (order)
2036 "This function returns the order function bases on its name."
2037 (cond
2038 ((null order) nil)
2039 ((symbolp order)
2040 (case order
2041 ((lex :lex $lex) #'lex>)
2042 ((grlex :grlex $grlex) #'grlex>)
2043 ((grevlex :grevlex $grevlex) #'grevlex>)
2044 ((invlex :invlex $invlex) #'invlex>)
2045 ((elimination-order-1 :elimination-order-1 elimination_order_1) #'elimination-order-1)
2046 (otherwise
2047 (mtell "~%Warning: Order ~M not found. Using default.~%" order))))
2049 (mtell "~%Order specification ~M is not recognized. Using default.~%" order)
2050 nil)))
2052 (defun find-ring (ring)
2053 "This function returns the ring structure bases on input symbol."
2054 (cond
2055 ((null ring) nil)
2056 ((symbolp ring)
2057 (case ring
2058 ((expression-ring :expression-ring $expression_ring) *expression-ring*)
2059 ((ring-of-integers :ring-of-integers $ring_of_integers) *ring-of-integers*)
2060 (otherwise
2061 (mtell "~%Warning: Ring ~M not found. Using default.~%" ring))))
2063 (mtell "~%Ring specification ~M is not recognized. Using default.~%" ring)
2064 nil)))
2066 (defmacro with-monomial-order ((order) &body body)
2067 "Evaluate BODY with monomial order set to ORDER."
2068 `(let ((*monomial-order* (or (find-order ,order) *monomial-order*)))
2069 . ,body))
2071 (defmacro with-coefficient-ring ((ring) &body body)
2072 "Evaluate BODY with coefficient ring set to RING."
2073 `(let ((*maxima-ring* (or (find-ring ,ring) *maxima-ring*)))
2074 . ,body))
2076 (defmacro with-elimination-orders ((primary secondary elimination-order)
2077 &body body)
2078 "Evaluate BODY with primary and secondary elimination orders set to PRIMARY and SECONDARY."
2079 `(let ((*primary-elimination-order* (or (find-order ,primary) *primary-elimination-order*))
2080 (*secondary-elimination-order* (or (find-order ,secondary) *secondary-elimination-order*))
2081 (*elimination-order* (or (find-order ,elimination-order) *elimination-order*)))
2082 . ,body))
2085 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2087 ;; Conversion from internal form to Maxima general form
2089 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2091 (defun maxima-head ()
2092 (if $poly_return_term_list
2093 '(mlist)
2094 '(mplus)))
2096 (defun coerce-to-maxima (poly-type object vars)
2097 (case poly-type
2098 (:polynomial
2099 `(,(maxima-head) ,@(mapcar #'(lambda (term) (coerce-to-maxima :term term vars)) (poly-termlist object))))
2100 (:poly-list
2101 `((mlist) ,@(mapcar #'(lambda (p) (coerce-to-maxima :polynomial p vars)) object)))
2102 (:term
2103 `((mtimes) ,(term-coeff object)
2104 ,@(mapcar #'(lambda (var power) `((mexpt) ,var ,power))
2105 vars (monom-exponents (term-monom object)))))
2106 (otherwise
2107 object)))
2110 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2112 ;; Macro facility for writing Maxima-level wrappers for
2113 ;; functions operating on internal representation
2115 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2117 (defmacro with-parsed-polynomials (((maxima-vars &optional (maxima-new-vars nil new-vars-supplied-p))
2118 &key (polynomials nil)
2119 (poly-lists nil)
2120 (poly-list-lists nil)
2121 (value-type nil))
2122 &body body
2123 &aux (vars (gensym))
2124 (new-vars (gensym)))
2125 `(let ((,vars (coerce-maxima-list ,maxima-vars))
2126 ,@(when new-vars-supplied-p
2127 (list `(,new-vars (coerce-maxima-list ,maxima-new-vars)))))
2128 (coerce-to-maxima
2129 ,value-type
2130 (with-coefficient-ring ($poly_coefficient_ring)
2131 (with-monomial-order ($poly_monomial_order)
2132 (with-elimination-orders ($poly_primary_elimination_order
2133 $poly_secondary_elimination_order
2134 $poly_elimination_order)
2135 (let ,(let ((args nil))
2136 (dolist (p polynomials args)
2137 (setf args (cons `(,p (parse-poly ,p ,vars)) args)))
2138 (dolist (p poly-lists args)
2139 (setf args (cons `(,p (parse-poly-list ,p ,vars)) args)))
2140 (dolist (p poly-list-lists args)
2141 (setf args (cons `(,p (parse-poly-list-list ,p ,vars)) args))))
2142 . ,body))))
2143 ,(if new-vars-supplied-p
2144 `(append ,vars ,new-vars)
2145 vars))))
2147 (defmacro define-unop (maxima-name fun-name
2148 &optional (documentation nil documentation-supplied-p))
2149 "Define a MAXIMA-level unary operator MAXIMA-NAME corresponding to unary function FUN-NAME."
2150 `(defun ,maxima-name (p vars
2151 &aux
2152 (vars (coerce-maxima-list vars))
2153 (p (parse-poly p vars)))
2154 ,@(when documentation-supplied-p (list documentation))
2155 (coerce-to-maxima :polynomial (,fun-name *maxima-ring* p) vars)))
2157 (defmacro define-binop (maxima-name fun-name
2158 &optional (documentation nil documentation-supplied-p))
2159 "Define a MAXIMA-level binary operator MAXIMA-NAME corresponding to binary function FUN-NAME."
2160 `(defmfun ,maxima-name (p q vars
2161 &aux
2162 (vars (coerce-maxima-list vars))
2163 (p (parse-poly p vars))
2164 (q (parse-poly q vars)))
2165 ,@(when documentation-supplied-p (list documentation))
2166 (coerce-to-maxima :polynomial (,fun-name *maxima-ring* p q) vars)))
2169 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2171 ;; Maxima-level interface functions
2173 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2175 ;; Auxiliary function for removing zero polynomial
2176 (defun remzero (plist) (remove #'poly-zerop plist))
2178 ;;Simple operators
2180 (define-binop $poly_add poly-add
2181 "Adds two polynomials P and Q")
2183 (define-binop $poly_subtract poly-sub
2184 "Subtracts a polynomial Q from P.")
2186 (define-binop $poly_multiply poly-mul
2187 "Returns the product of polynomials P and Q.")
2189 (define-binop $poly_s_polynomial spoly
2190 "Returns the syzygy polynomial (S-polynomial) of two polynomials P and Q.")
2192 (define-unop $poly_primitive_part poly-primitive-part
2193 "Returns the polynomial P divided by GCD of its coefficients.")
2195 (define-unop $poly_normalize poly-normalize
2196 "Returns the polynomial P divided by the leading coefficient.")
2198 ;;Functions
2200 (defmfun $poly_expand (p vars)
2201 "This function is equivalent to EXPAND(P) if P parses correctly to a polynomial.
2202 If the representation is not compatible with a polynomial in variables VARS,
2203 the result is an error."
2204 (with-parsed-polynomials ((vars) :polynomials (p)
2205 :value-type :polynomial)
2208 (defmfun $poly_expt (p n vars)
2209 (with-parsed-polynomials ((vars) :polynomials (p) :value-type :polynomial)
2210 (poly-expt *maxima-ring* p n)))
2212 (defmfun $poly_content (p vars)
2213 (with-parsed-polynomials ((vars) :polynomials (p))
2214 (poly-content *maxima-ring* p)))
2216 (defmfun $poly_pseudo_divide (f fl vars
2217 &aux (vars (coerce-maxima-list vars))
2218 (f (parse-poly f vars))
2219 (fl (parse-poly-list fl vars)))
2220 (multiple-value-bind (quot rem c division-count)
2221 (poly-pseudo-divide *maxima-ring* f fl)
2222 `((mlist)
2223 ,(coerce-to-maxima :poly-list quot vars)
2224 ,(coerce-to-maxima :polynomial rem vars)
2226 ,division-count)))
2228 (defmfun $poly_exact_divide (f g vars)
2229 (with-parsed-polynomials ((vars) :polynomials (f g) :value-type :polynomial)
2230 (poly-exact-divide *maxima-ring* f g)))
2232 (defmfun $poly_normal_form (f fl vars)
2233 (with-parsed-polynomials ((vars) :polynomials (f)
2234 :poly-lists (fl)
2235 :value-type :polynomial)
2236 (normal-form *maxima-ring* f (remzero fl) nil)))
2238 (defmfun $poly_buchberger_criterion (g vars)
2239 (with-parsed-polynomials ((vars) :poly-lists (g))
2240 (buchberger-criterion *maxima-ring* g)))
2242 (defmfun $poly_buchberger (fl vars)
2243 (with-parsed-polynomials ((vars) :poly-lists (fl) :value-type :poly-list)
2244 (buchberger *maxima-ring* (remzero fl) 0 nil)))
2246 (defmfun $poly_reduction (plist vars)
2247 (with-parsed-polynomials ((vars) :poly-lists (plist)
2248 :value-type :poly-list)
2249 (reduction *maxima-ring* plist)))
2251 (defmfun $poly_minimization (plist vars)
2252 (with-parsed-polynomials ((vars) :poly-lists (plist)
2253 :value-type :poly-list)
2254 (minimization plist)))
2256 (defmfun $poly_normalize_list (plist vars)
2257 (with-parsed-polynomials ((vars) :poly-lists (plist)
2258 :value-type :poly-list)
2259 (poly-normalize-list *maxima-ring* plist)))
2261 (defmfun $poly_grobner (f vars)
2262 (with-parsed-polynomials ((vars) :poly-lists (f)
2263 :value-type :poly-list)
2264 (grobner *maxima-ring* (remzero f))))
2266 (defmfun $poly_reduced_grobner (f vars)
2267 (with-parsed-polynomials ((vars) :poly-lists (f)
2268 :value-type :poly-list)
2269 (reduced-grobner *maxima-ring* (remzero f))))
2271 (defmfun $poly_depends_p (p var mvars
2272 &aux (vars (coerce-maxima-list mvars))
2273 (pos (position var vars)))
2274 (if (null pos)
2275 (merror "~%Variable ~M not in the list of variables ~M." var mvars)
2276 (poly-depends-p (parse-poly p vars) pos)))
2278 (defmfun $poly_elimination_ideal (flist k vars)
2279 (with-parsed-polynomials ((vars) :poly-lists (flist)
2280 :value-type :poly-list)
2281 (elimination-ideal *maxima-ring* flist k nil 0)))
2283 (defmfun $poly_colon_ideal (f g vars)
2284 (with-parsed-polynomials ((vars) :poly-lists (f g) :value-type :poly-list)
2285 (colon-ideal *maxima-ring* f g nil)))
2287 (defmfun $poly_ideal_intersection (f g vars)
2288 (with-parsed-polynomials ((vars) :poly-lists (f g) :value-type :poly-list)
2289 (ideal-intersection *maxima-ring* f g nil)))
2291 (defmfun $poly_lcm (f g vars)
2292 (with-parsed-polynomials ((vars) :polynomials (f g) :value-type :polynomial)
2293 (poly-lcm *maxima-ring* f g)))
2295 (defmfun $poly_gcd (f g vars)
2296 ($first ($divide (m* f g) ($poly_lcm f g vars))))
2298 (defmfun $poly_grobner_equal (g1 g2 vars)
2299 (with-parsed-polynomials ((vars) :poly-lists (g1 g2))
2300 (grobner-equal *maxima-ring* g1 g2)))
2302 (defmfun $poly_grobner_subsetp (g1 g2 vars)
2303 (with-parsed-polynomials ((vars) :poly-lists (g1 g2))
2304 (grobner-subsetp *maxima-ring* g1 g2)))
2306 (defmfun $poly_grobner_member (p g vars)
2307 (with-parsed-polynomials ((vars) :polynomials (p) :poly-lists (g))
2308 (grobner-member *maxima-ring* p g)))
2310 (defmfun $poly_ideal_saturation1 (f p vars)
2311 (with-parsed-polynomials ((vars) :poly-lists (f) :polynomials (p)
2312 :value-type :poly-list)
2313 (ideal-saturation-1 *maxima-ring* f p 0)))
2315 (defmfun $poly_saturation_extension (f plist vars new-vars)
2316 (with-parsed-polynomials ((vars new-vars)
2317 :poly-lists (f plist)
2318 :value-type :poly-list)
2319 (saturation-extension *maxima-ring* f plist)))
2321 (defmfun $poly_polysaturation_extension (f plist vars new-vars)
2322 (with-parsed-polynomials ((vars new-vars)
2323 :poly-lists (f plist)
2324 :value-type :poly-list)
2325 (polysaturation-extension *maxima-ring* f plist)))
2327 (defmfun $poly_ideal_polysaturation1 (f plist vars)
2328 (with-parsed-polynomials ((vars) :poly-lists (f plist)
2329 :value-type :poly-list)
2330 (ideal-polysaturation-1 *maxima-ring* f plist 0 nil)))
2332 (defmfun $poly_ideal_saturation (f g vars)
2333 (with-parsed-polynomials ((vars) :poly-lists (f g)
2334 :value-type :poly-list)
2335 (ideal-saturation *maxima-ring* f g 0 nil)))
2337 (defmfun $poly_ideal_polysaturation (f ideal-list vars)
2338 (with-parsed-polynomials ((vars) :poly-lists (f)
2339 :poly-list-lists (ideal-list)
2340 :value-type :poly-list)
2341 (ideal-polysaturation *maxima-ring* f ideal-list 0 nil)))