close Warning: Can't synchronize with repository "(default)" (The repository directory has changed, you should resynchronize the repository with: trac-admin $ENV repository resync '(default)'). Look in the Trac log for more information.

source: grobner.lisp@ 1

Last change on this file since 1 was 1, checked in by Marek Rychlik, 15 years ago

Moved from RCS.
The code does not contain any non-portable optimizations.

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