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: branches/f4grobner/grobner.lisp@ 46

Last change on this file since 46 was 46, checked in by Marek Rychlik, 9 years ago

* empty log message *

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