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@ 65

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

* empty log message *

File size: 36.2 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/06/02 0:34:17 $"))
31
32;;FUNCTS is loaded because it contains the definition of LCM
33($load "functs")
34
35
36
37
38
39
40;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
41;;
42;; Global switches
43;; (Can be used in Maxima just fine)
44;;
45;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
46
47(defmvar $poly_monomial_order '$lex
48 "This switch controls which monomial order is used in polynomial
49and Grobner basis calculations. If not set, LEX will be used")
50
51(defmvar $poly_coefficient_ring '$expression_ring
52 "This switch indicates the coefficient ring of the polynomials
53that will be used in grobner calculations. If not set, Maxima's
54general expression ring will be used. This variable may be set
55to RING_OF_INTEGERS if desired.")
56
57(defmvar $poly_primary_elimination_order nil
58 "Name of the default order for eliminated variables in elimination-based functions.
59If not set, LEX will be used.")
60
61(defmvar $poly_secondary_elimination_order nil
62 "Name of the default order for kept variables in elimination-based functions.
63If not set, LEX will be used.")
64
65(defmvar $poly_elimination_order nil
66 "Name of the default elimination order used in elimination calculations.
67If set, it overrides the settings in variables POLY_PRIMARY_ELIMINATION_ORDER
68and SECONDARY_ELIMINATION_ORDER. The user must ensure that this is a true
69elimination order valid for the number of eliminated variables.")
70
71(defmvar $poly_return_term_list nil
72 "If set to T, all functions in this package will return each polynomial as a
73list of terms in the current monomial order rather than a Maxima general expression.")
74
75(defmvar $poly_grobner_debug nil
76 "If set to TRUE, produce debugging and tracing output.")
77
78(defmvar $poly_grobner_algorithm '$buchberger
79 "The name of the algorithm used to find grobner bases.")
80
81(defmvar $poly_top_reduction_only nil
82 "If not FALSE, use top reduction only whenever possible.
83Top reduction means that division algorithm stops after the first reduction.")
84
85
86
87;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
88;;
89;; Coefficient ring operations
90;;
91;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
92;;
93;; These are ALL operations that are performed on the coefficients by
94;; the package, and thus the coefficient ring can be changed by merely
95;; redefining these operations.
96;;
97;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
98
99(defstruct (ring)
100 (parse #'identity :type function)
101 (unit #'identity :type function)
102 (zerop #'identity :type function)
103 (add #'identity :type function)
104 (sub #'identity :type function)
105 (uminus #'identity :type function)
106 (mul #'identity :type function)
107 (div #'identity :type function)
108 (lcm #'identity :type function)
109 (ezgcd #'identity :type function)
110 (gcd #'identity :type function))
111
112(defparameter *ring-of-integers*
113 (make-ring
114 :parse #'identity
115 :unit #'(lambda () 1)
116 :zerop #'zerop
117 :add #'+
118 :sub #'-
119 :uminus #'-
120 :mul #'*
121 :div #'/
122 :lcm #'lcm
123 :ezgcd #'(lambda (x y &aux (c (gcd x y))) (values c (/ x c) (/ y c)))
124 :gcd #'gcd)
125 "The ring of integers.")
126
127
128
129;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
130;;
131;; This is how we perform operations on coefficients
132;; using Maxima functions.
133;;
134;; Functions and macros dealing with internal representation structure
135;;
136;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
137
138
139
140
141;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
142;;
143;; Low-level polynomial arithmetic done on
144;; lists of terms
145;;
146;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
147
148(defmacro termlist-lt (p) `(car ,p))
149(defun termlist-lm (p) (term-monom (termlist-lt p)))
150(defun termlist-lc (p) (term-coeff (termlist-lt p)))
151
152(define-modify-macro scalar-mul (c) coeff-mul)
153
154(defun scalar-times-termlist (ring c p)
155 "Multiply scalar C by a polynomial P. This function works
156even if there are divisors of 0."
157 (mapcan
158 #'(lambda (term)
159 (let ((c1 (funcall (ring-mul ring) c (term-coeff term))))
160 (unless (funcall (ring-zerop ring) c1)
161 (list (make-term (term-monom term) c1)))))
162 p))
163
164
165(defun term-mul (ring term1 term2)
166 "Returns (LIST TERM) wheter TERM is the product of the terms TERM1 TERM2,
167or NIL when the product is 0. This definition takes care of divisors of 0
168in the coefficient ring."
169 (let ((c (funcall (ring-mul ring) (term-coeff term1) (term-coeff term2))))
170 (unless (funcall (ring-zerop ring) c)
171 (list (make-term (monom-mul (term-monom term1) (term-monom term2)) c)))))
172
173(defun term-times-termlist (ring term f)
174 (declare (type ring ring))
175 (mapcan #'(lambda (term-f) (term-mul ring term term-f)) f))
176
177(defun termlist-times-term (ring f term)
178 (mapcan #'(lambda (term-f) (term-mul ring term-f term)) f))
179
180(defun monom-times-term (m term)
181 (make-term (monom-mul m (term-monom term)) (term-coeff term)))
182
183(defun monom-times-termlist (m f)
184 (cond
185 ((null f) nil)
186 (t
187 (mapcar #'(lambda (x) (monom-times-term m x)) f))))
188
189(defun termlist-uminus (ring f)
190 (mapcar #'(lambda (x)
191 (make-term (term-monom x) (funcall (ring-uminus ring) (term-coeff x))))
192 f))
193
194(defun termlist-add (ring p q)
195 (declare (type list p q))
196 (do (r)
197 ((cond
198 ((endp p)
199 (setf r (revappend r q)) t)
200 ((endp q)
201 (setf r (revappend r p)) t)
202 (t
203 (multiple-value-bind
204 (lm-greater lm-equal)
205 (monomial-order (termlist-lm p) (termlist-lm q))
206 (cond
207 (lm-equal
208 (let ((s (funcall (ring-add ring) (termlist-lc p) (termlist-lc q))))
209 (unless (funcall (ring-zerop ring) s) ;check for cancellation
210 (setf r (cons (make-term (termlist-lm p) s) r)))
211 (setf p (cdr p) q (cdr q))))
212 (lm-greater
213 (setf r (cons (car p) r)
214 p (cdr p)))
215 (t (setf r (cons (car q) r)
216 q (cdr q)))))
217 nil))
218 r)))
219
220(defun termlist-sub (ring p q)
221 (declare (type list p q))
222 (do (r)
223 ((cond
224 ((endp p)
225 (setf r (revappend r (termlist-uminus ring q)))
226 t)
227 ((endp q)
228 (setf r (revappend r p))
229 t)
230 (t
231 (multiple-value-bind
232 (mgreater mequal)
233 (monomial-order (termlist-lm p) (termlist-lm q))
234 (cond
235 (mequal
236 (let ((s (funcall (ring-sub ring) (termlist-lc p) (termlist-lc q))))
237 (unless (funcall (ring-zerop ring) s) ;check for cancellation
238 (setf r (cons (make-term (termlist-lm p) s) r)))
239 (setf p (cdr p) q (cdr q))))
240 (mgreater
241 (setf r (cons (car p) r)
242 p (cdr p)))
243 (t (setf r (cons (make-term (termlist-lm q) (funcall (ring-uminus ring) (termlist-lc q))) r)
244 q (cdr q)))))
245 nil))
246 r)))
247
248;; Multiplication of polynomials
249;; Non-destructive version
250(defun termlist-mul (ring p q)
251 (cond ((or (endp p) (endp q)) nil) ;p or q is 0 (represented by NIL)
252 ;; If p=p0+p1 and q=q0+q1 then pq=p0q0+p0q1+p1q
253 ((endp (cdr p))
254 (term-times-termlist ring (car p) q))
255 ((endp (cdr q))
256 (termlist-times-term ring p (car q)))
257 (t
258 (let ((head (term-mul ring (termlist-lt p) (termlist-lt q)))
259 (tail (termlist-add ring (term-times-termlist ring (car p) (cdr q))
260 (termlist-mul ring (cdr p) q))))
261 (cond ((null head) tail)
262 ((null tail) head)
263 (t (nconc head tail)))))))
264
265(defun termlist-unit (ring dimension)
266 (declare (fixnum dimension))
267 (list (make-term (make-monom dimension :initial-element 0)
268 (funcall (ring-unit ring)))))
269
270(defun termlist-expt (ring poly n &aux (dim (monom-dimension (termlist-lm poly))))
271 (declare (type fixnum n dim))
272 (cond
273 ((minusp n) (error "termlist-expt: Negative exponent."))
274 ((endp poly) (if (zerop n) (termlist-unit ring dim) nil))
275 (t
276 (do ((k 1 (ash k 1))
277 (q poly (termlist-mul ring q q)) ;keep squaring
278 (p (termlist-unit ring dim) (if (not (zerop (logand k n))) (termlist-mul ring p q) p)))
279 ((> k n) p)
280 (declare (fixnum k))))))
281
282
283
284
285
286
287;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
288;;
289;; Debugging/tracing
290;;
291;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
292(defmacro debug-cgb (&rest args)
293 `(when $poly_grobner_debug (format *terminal-io* ,@args)))
294
295
296
297
298
299;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
300;;
301;; These are provided mostly for debugging purposes To enable
302;; verification of grobner bases with BUCHBERGER-CRITERION, do
303;; (pushnew :grobner-check *features*) and compile/load this file.
304;; With this feature, the calculations will slow down CONSIDERABLY.
305;;
306;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
307
308(defun grobner-test (ring g f)
309 "Test whether G is a Grobner basis and F is contained in G. Return T
310upon success and NIL otherwise."
311 (debug-cgb "~&GROBNER CHECK: ")
312 (let (($poly_grobner_debug nil)
313 (stat1 (buchberger-criterion ring g))
314 (stat2
315 (every #'poly-zerop
316 (makelist (normal-form ring (copy-tree (elt f i)) g nil)
317 (i 0 (1- (length f)))))))
318 (unless stat1 (error "~&Buchberger criterion failed."))
319 (unless stat2
320 (error "~&Original polys not in ideal spanned by Grobner.")))
321 (debug-cgb "~&GROBNER CHECK END")
322 t)
323
324
325(defun find-grobner-function (algorithm)
326 "Return a function which calculates Grobner basis, based on its
327names. Names currently used are either Lisp symbols, Maxima symbols or
328keywords."
329 (ecase algorithm
330 ((buchberger :buchberger $buchberger) #'buchberger)
331 ((parallel-buchberger :parallel-buchberger $parallel_buchberger) #'parallel-buchberger)
332 ((gebauer-moeller :gebauer_moeller $gebauer_moeller) #'gebauer-moeller)))
333
334(defun grobner (ring f &optional (start 0) (top-reduction-only nil))
335 ;;(setf F (sort F #'< :key #'sugar))
336 (funcall
337 (find-grobner-function $poly_grobner_algorithm)
338 ring f start top-reduction-only))
339
340(defun reduced-grobner (ring f &optional (start 0) (top-reduction-only $poly_top_reduction_only))
341 (reduction ring (grobner ring f start top-reduction-only)))
342
343(defun set-pair-heuristic (method)
344 "Sets up variables *PAIR-KEY-FUNCTION* and *PAIR-ORDER* used
345to determine the priority of critical pairs in the priority queue."
346 (ecase method
347 ((sugar :sugar $sugar)
348 (setf *pair-key-function* #'sugar-pair-key
349 *pair-order* #'sugar-order))
350; ((minimal-mock-spoly :minimal-mock-spoly $minimal_mock_spoly)
351; (setf *pair-key-function* #'mock-spoly
352; *pair-order* #'mock-spoly-order))
353 ((minimal-lcm :minimal-lcm $minimal_lcm)
354 (setf *pair-key-function* #'(lambda (p q)
355 (monom-lcm (poly-lm p) (poly-lm q)))
356 *pair-order* #'reverse-monomial-order))
357 ((minimal-total-degree :minimal-total-degree $minimal_total_degree)
358 (setf *pair-key-function* #'(lambda (p q)
359 (monom-total-degree
360 (monom-lcm (poly-lm p) (poly-lm q))))
361 *pair-order* #'<))
362 ((minimal-length :minimal-length $minimal_length)
363 (setf *pair-key-function* #'(lambda (p q)
364 (+ (poly-length p) (poly-length q)))
365 *pair-order* #'<))))
366
367
368
369;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
370;;
371;; Operations in ideal theory
372;;
373;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
374
375;; Does the term depend on variable K?
376(defun term-depends-p (term k)
377 "Return T if the term TERM depends on variable number K."
378 (monom-depends-p (term-monom term) k))
379
380;; Does the polynomial P depend on variable K?
381(defun poly-depends-p (p k)
382 "Return T if the term polynomial P depends on variable number K."
383 (some #'(lambda (term) (term-depends-p term k)) (poly-termlist p)))
384
385(defun ring-intersection (plist k)
386 "This function assumes that polynomial list PLIST is a Grobner basis
387and it calculates the intersection with the ring R[x[k+1],...,x[n]], i.e.
388it discards polynomials which depend on variables x[0], x[1], ..., x[k]."
389 (dotimes (i k plist)
390 (setf plist
391 (remove-if #'(lambda (p)
392 (poly-depends-p p i))
393 plist))))
394
395(defun elimination-ideal (ring flist k
396 &optional (top-reduction-only $poly_top_reduction_only) (start 0)
397 &aux (*monomial-order*
398 (or *elimination-order*
399 (elimination-order k))))
400 (ring-intersection (reduced-grobner ring flist start top-reduction-only) k))
401
402(defun colon-ideal (ring f g &optional (top-reduction-only $poly_top_reduction_only))
403 "Returns the reduced Grobner basis of the colon ideal Id(F):Id(G),
404where F and G are two lists of polynomials. The colon ideal I:J is
405defined as the set of polynomials H such that for all polynomials W in
406J the polynomial W*H belongs to I."
407 (cond
408 ((endp g)
409 ;;Id(G) consists of 0 only so W*0=0 belongs to Id(F)
410 (if (every #'poly-zerop f)
411 (error "First ideal must be non-zero.")
412 (list (make-poly
413 (list (make-term
414 (make-monom (monom-dimension (poly-lm (find-if-not #'poly-zerop f)))
415 :initial-element 0)
416 (funcall (ring-unit ring))))))))
417 ((endp (cdr g))
418 (colon-ideal-1 ring f (car g) top-reduction-only))
419 (t
420 (ideal-intersection ring
421 (colon-ideal-1 ring f (car g) top-reduction-only)
422 (colon-ideal ring f (rest g) top-reduction-only)
423 top-reduction-only))))
424
425(defun colon-ideal-1 (ring f g &optional (top-reduction-only $poly_top_reduction_only))
426 "Returns the reduced Grobner basis of the colon ideal Id(F):Id({G}), where
427F is a list of polynomials and G is a polynomial."
428 (mapcar #'(lambda (x) (poly-exact-divide ring x g)) (ideal-intersection ring f (list g) top-reduction-only)))
429
430
431(defun ideal-intersection (ring f g &optional (top-reduction-only $poly_top_reduction_only)
432 &aux (*monomial-order* (or *elimination-order*
433 #'elimination-order-1)))
434 (mapcar #'poly-contract
435 (ring-intersection
436 (reduced-grobner
437 ring
438 (append (mapcar #'(lambda (p) (poly-extend p (make-monom 1 :initial-element 1))) f)
439 (mapcar #'(lambda (p)
440 (poly-append (poly-extend (poly-uminus ring p)
441 (make-monom 1 :initial-element 1))
442 (poly-extend p)))
443 g))
444 0
445 top-reduction-only)
446 1)))
447
448(defun poly-lcm (ring f g)
449 "Return LCM (least common multiple) of two polynomials F and G.
450The polynomials must be ordered according to monomial order PRED
451and their coefficients must be compatible with the RING structure
452defined in the COEFFICIENT-RING package."
453 (cond
454 ((poly-zerop f) f)
455 ((poly-zerop g) g)
456 ((and (endp (cdr (poly-termlist f))) (endp (cdr (poly-termlist g))))
457 (let ((m (monom-lcm (poly-lm f) (poly-lm g))))
458 (make-poly-from-termlist (list (make-term m (funcall (ring-lcm ring) (poly-lc f) (poly-lc g)))))))
459 (t
460 (multiple-value-bind (f f-cont)
461 (poly-primitive-part ring f)
462 (multiple-value-bind (g g-cont)
463 (poly-primitive-part ring g)
464 (scalar-times-poly
465 ring
466 (funcall (ring-lcm ring) f-cont g-cont)
467 (poly-primitive-part ring (car (ideal-intersection ring (list f) (list g) nil)))))))))
468
469;; Do two Grobner bases yield the same ideal?
470(defun grobner-equal (ring g1 g2)
471 "Returns T if two lists of polynomials G1 and G2, assumed to be Grobner bases,
472generate the same ideal, and NIL otherwise."
473 (and (grobner-subsetp ring g1 g2) (grobner-subsetp ring g2 g1)))
474
475(defun grobner-subsetp (ring g1 g2)
476 "Returns T if a list of polynomials G1 generates
477an ideal contained in the ideal generated by a polynomial list G2,
478both G1 and G2 assumed to be Grobner bases. Returns NIL otherwise."
479 (every #'(lambda (p) (grobner-member ring p g2)) g1))
480
481(defun grobner-member (ring p g)
482 "Returns T if a polynomial P belongs to the ideal generated by the
483polynomial list G, which is assumed to be a Grobner basis. Returns NIL otherwise."
484 (poly-zerop (normal-form ring p g nil)))
485
486;; Calculate F : p^inf
487(defun ideal-saturation-1 (ring f p start &optional (top-reduction-only $poly_top_reduction_only)
488 &aux (*monomial-order* (or *elimination-order*
489 #'elimination-order-1)))
490 "Returns the reduced Grobner basis of the saturation of the ideal
491generated by a polynomial list F in the ideal generated by a single
492polynomial P. The saturation ideal is defined as the set of
493polynomials H such for some natural number n (* (EXPT P N) H) is in the ideal
494F. Geometrically, over an algebraically closed field, this is the set
495of polynomials in the ideal generated by F which do not identically
496vanish on the variety of P."
497 (mapcar
498 #'poly-contract
499 (ring-intersection
500 (reduced-grobner
501 ring
502 (saturation-extension-1 ring f p)
503 start top-reduction-only)
504 1)))
505
506
507
508;; Calculate F : p1^inf : p2^inf : ... : ps^inf
509(defun ideal-polysaturation-1 (ring f plist start &optional (top-reduction-only $poly_top_reduction_only))
510 "Returns the reduced Grobner basis of the ideal obtained by a
511sequence of successive saturations in the polynomials
512of the polynomial list PLIST of the ideal generated by the
513polynomial list F."
514 (cond
515 ((endp plist) (reduced-grobner ring f start top-reduction-only))
516 (t (let ((g (ideal-saturation-1 ring f (car plist) start top-reduction-only)))
517 (ideal-polysaturation-1 ring g (rest plist) (length g) top-reduction-only)))))
518
519(defun ideal-saturation (ring f g start &optional (top-reduction-only $poly_top_reduction_only)
520 &aux
521 (k (length g))
522 (*monomial-order* (or *elimination-order*
523 (elimination-order k))))
524 "Returns the reduced Grobner basis of the saturation of the ideal
525generated by a polynomial list F in the ideal generated a polynomial
526list G. The saturation ideal is defined as the set of polynomials H
527such for some natural number n and some P in the ideal generated by G
528the polynomial P**N * H is in the ideal spanned by F. Geometrically,
529over an algebraically closed field, this is the set of polynomials in
530the ideal generated by F which do not identically vanish on the
531variety of G."
532 (mapcar
533 #'(lambda (q) (poly-contract q k))
534 (ring-intersection
535 (reduced-grobner ring
536 (polysaturation-extension ring f g)
537 start
538 top-reduction-only)
539 k)))
540
541(defun ideal-polysaturation (ring f ideal-list start &optional (top-reduction-only $poly_top_reduction_only))
542 "Returns the reduced Grobner basis of the ideal obtained by a
543successive applications of IDEAL-SATURATION to F and lists of
544polynomials in the list IDEAL-LIST."
545 (cond
546 ((endp ideal-list) f)
547 (t (let ((h (ideal-saturation ring f (car ideal-list) start top-reduction-only)))
548 (ideal-polysaturation ring h (rest ideal-list) (length h) top-reduction-only)))))
549
550
551
552;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
553;;
554;; Set up the coefficients to be polynomials
555;;
556;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
557
558;; (defun poly-ring (ring vars)
559;; (make-ring
560;; :parse #'(lambda (expr) (poly-eval ring expr vars))
561;; :unit #'(lambda () (poly-unit ring (length vars)))
562;; :zerop #'poly-zerop
563;; :add #'(lambda (x y) (poly-add ring x y))
564;; :sub #'(lambda (x y) (poly-sub ring x y))
565;; :uminus #'(lambda (x) (poly-uminus ring x))
566;; :mul #'(lambda (x y) (poly-mul ring x y))
567;; :div #'(lambda (x y) (poly-exact-divide ring x y))
568;; :lcm #'(lambda (x y) (poly-lcm ring x y))
569;; :ezgcd #'(lambda (x y &aux (gcd (poly-gcd ring x y)))
570;; (values gcd
571;; (poly-exact-divide ring x gcd)
572;; (poly-exact-divide ring y gcd)))
573;; :gcd #'(lambda (x y) (poly-gcd x y))))
574
575
576
577;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
578;;
579;; Conversion from internal to infix form
580;;
581;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
582
583(defun coerce-to-infix (poly-type object vars)
584 (case poly-type
585 (:termlist
586 `(+ ,@(mapcar #'(lambda (term) (coerce-to-infix :term term vars)) object)))
587 (:polynomial
588 (coerce-to-infix :termlist (poly-termlist object) vars))
589 (:poly-list
590 `([ ,@(mapcar #'(lambda (p) (coerce-to-infix :polynomial p vars)) object)))
591 (:term
592 `(* ,(term-coeff object)
593 ,@(mapcar #'(lambda (var power) `(expt ,var ,power))
594 vars (monom-exponents (term-monom object)))))
595 (otherwise
596 object)))
597
598
599
600;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
601;;
602;; Maxima expression ring
603;;
604;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
605
606(defparameter *expression-ring*
607 (make-ring
608 ;;(defun coeff-zerop (expr) (meval1 `(($is) (($equal) ,expr 0))))
609 :parse #'(lambda (expr)
610 (when modulus (setf expr ($rat expr)))
611 expr)
612 :unit #'(lambda () (if modulus ($rat 1) 1))
613 :zerop #'(lambda (expr)
614 ;;When is exactly a maxima expression equal to 0?
615 (cond ((numberp expr)
616 (= expr 0))
617 ((atom expr) nil)
618 (t
619 (case (caar expr)
620 (mrat (eql ($ratdisrep expr) 0))
621 (otherwise (eql ($totaldisrep expr) 0))))))
622 :add #'(lambda (x y) (m+ x y))
623 :sub #'(lambda (x y) (m- x y))
624 :uminus #'(lambda (x) (m- x))
625 :mul #'(lambda (x y) (m* x y))
626 ;;(defun coeff-div (x y) (cadr ($divide x y)))
627 :div #'(lambda (x y) (m// x y))
628 :lcm #'(lambda (x y) (meval1 `((|$LCM|) ,x ,y)))
629 :ezgcd #'(lambda (x y) (apply #'values (cdr ($ezgcd ($totaldisrep x) ($totaldisrep y)))))
630 ;; :gcd #'(lambda (x y) (second ($ezgcd x y)))))
631 :gcd #'(lambda (x y) ($gcd x y))))
632
633(defvar *maxima-ring* *expression-ring*
634 "The ring of coefficients, over which all polynomials
635are assumed to be defined.")
636
637
638
639;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
640;;
641;; Maxima expression parsing
642;;
643;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
644
645(defun equal-test-p (expr1 expr2)
646 (alike1 expr1 expr2))
647
648(defun coerce-maxima-list (expr)
649 "convert a maxima list to lisp list."
650 (cond
651 ((and (consp (car expr)) (eql (caar expr) 'mlist)) (cdr expr))
652 (t expr)))
653
654(defun free-of-vars (expr vars) (apply #'$freeof `(,@vars ,expr)))
655
656(defun parse-poly (expr vars &aux (vars (coerce-maxima-list vars)))
657 "Convert a maxima polynomial expression EXPR in variables VARS to internal form."
658 (labels ((parse (arg) (parse-poly arg vars))
659 (parse-list (args) (mapcar #'parse args)))
660 (cond
661 ((eql expr 0) (make-poly-zero))
662 ((member expr vars :test #'equal-test-p)
663 (let ((pos (position expr vars :test #'equal-test-p)))
664 (make-variable *maxima-ring* (length vars) pos)))
665 ((free-of-vars expr vars)
666 ;;This means that variable-free CRE and Poisson forms will be converted
667 ;;to coefficients intact
668 (coerce-coeff *maxima-ring* expr vars))
669 (t
670 (case (caar expr)
671 (mplus (reduce #'(lambda (x y) (poly-add *maxima-ring* x y)) (parse-list (cdr expr))))
672 (mminus (poly-uminus *maxima-ring* (parse (cadr expr))))
673 (mtimes
674 (if (endp (cddr expr)) ;unary
675 (parse (cdr expr))
676 (reduce #'(lambda (p q) (poly-mul *maxima-ring* p q)) (parse-list (cdr expr)))))
677 (mexpt
678 (cond
679 ((member (cadr expr) vars :test #'equal-test-p)
680 ;;Special handling of (expt var pow)
681 (let ((pos (position (cadr expr) vars :test #'equal-test-p)))
682 (make-variable *maxima-ring* (length vars) pos (caddr expr))))
683 ((not (and (integerp (caddr expr)) (plusp (caddr expr))))
684 ;; Negative power means division in coefficient ring
685 ;; Non-integer power means non-polynomial coefficient
686 (mtell "~%Warning: Expression ~%~M~%contains power which is not a positive integer. Parsing as coefficient.~%"
687 expr)
688 (coerce-coeff *maxima-ring* expr vars))
689 (t (poly-expt *maxima-ring* (parse (cadr expr)) (caddr expr)))))
690 (mrat (parse ($ratdisrep expr)))
691 (mpois (parse ($outofpois expr)))
692 (otherwise
693 (coerce-coeff *maxima-ring* expr vars)))))))
694
695(defun parse-poly-list (expr vars)
696 (case (caar expr)
697 (mlist (mapcar #'(lambda (p) (parse-poly p vars)) (cdr expr)))
698 (t (merror "Expression ~M is not a list of polynomials in variables ~M."
699 expr vars))))
700(defun parse-poly-list-list (poly-list-list vars)
701 (mapcar #'(lambda (g) (parse-poly-list g vars)) (coerce-maxima-list poly-list-list)))
702
703
704
705;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
706;;
707;; Order utilities
708;;
709;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
710(defun find-order (order)
711 "This function returns the order function bases on its name."
712 (cond
713 ((null order) nil)
714 ((symbolp order)
715 (case order
716 ((lex :lex $lex) #'lex>)
717 ((grlex :grlex $grlex) #'grlex>)
718 ((grevlex :grevlex $grevlex) #'grevlex>)
719 ((invlex :invlex $invlex) #'invlex>)
720 ((elimination-order-1 :elimination-order-1 elimination_order_1) #'elimination-order-1)
721 (otherwise
722 (mtell "~%Warning: Order ~M not found. Using default.~%" order))))
723 (t
724 (mtell "~%Order specification ~M is not recognized. Using default.~%" order)
725 nil)))
726
727(defun find-ring (ring)
728 "This function returns the ring structure bases on input symbol."
729 (cond
730 ((null ring) nil)
731 ((symbolp ring)
732 (case ring
733 ((expression-ring :expression-ring $expression_ring) *expression-ring*)
734 ((ring-of-integers :ring-of-integers $ring_of_integers) *ring-of-integers*)
735 (otherwise
736 (mtell "~%Warning: Ring ~M not found. Using default.~%" ring))))
737 (t
738 (mtell "~%Ring specification ~M is not recognized. Using default.~%" ring)
739 nil)))
740
741(defmacro with-monomial-order ((order) &body body)
742 "Evaluate BODY with monomial order set to ORDER."
743 `(let ((*monomial-order* (or (find-order ,order) *monomial-order*)))
744 . ,body))
745
746(defmacro with-coefficient-ring ((ring) &body body)
747 "Evaluate BODY with coefficient ring set to RING."
748 `(let ((*maxima-ring* (or (find-ring ,ring) *maxima-ring*)))
749 . ,body))
750
751(defmacro with-elimination-orders ((primary secondary elimination-order)
752 &body body)
753 "Evaluate BODY with primary and secondary elimination orders set to PRIMARY and SECONDARY."
754 `(let ((*primary-elimination-order* (or (find-order ,primary) *primary-elimination-order*))
755 (*secondary-elimination-order* (or (find-order ,secondary) *secondary-elimination-order*))
756 (*elimination-order* (or (find-order ,elimination-order) *elimination-order*)))
757 . ,body))
758
759
760
761;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
762;;
763;; Conversion from internal form to Maxima general form
764;;
765;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
766
767(defun maxima-head ()
768 (if $poly_return_term_list
769 '(mlist)
770 '(mplus)))
771
772(defun coerce-to-maxima (poly-type object vars)
773 (case poly-type
774 (:polynomial
775 `(,(maxima-head) ,@(mapcar #'(lambda (term) (coerce-to-maxima :term term vars)) (poly-termlist object))))
776 (:poly-list
777 `((mlist) ,@(mapcar #'(lambda (p) ($ratdisrep (coerce-to-maxima :polynomial p vars))) object)))
778 (:term
779 `((mtimes) ,($ratdisrep (term-coeff object))
780 ,@(mapcar #'(lambda (var power) `((mexpt) ,var ,power))
781 vars (monom-exponents (term-monom object)))))
782 ;; Assumes that Lisp and Maxima logicals coincide
783 (:logical object)
784 (otherwise
785 object)))
786
787
788
789;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
790;;
791;; Macro facility for writing Maxima-level wrappers for
792;; functions operating on internal representation
793;;
794;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
795
796(defmacro with-parsed-polynomials (((maxima-vars &optional (maxima-new-vars nil new-vars-supplied-p))
797 &key (polynomials nil)
798 (poly-lists nil)
799 (poly-list-lists nil)
800 (value-type nil))
801 &body body
802 &aux (vars (gensym))
803 (new-vars (gensym)))
804 `(let ((,vars (coerce-maxima-list ,maxima-vars))
805 ,@(when new-vars-supplied-p
806 (list `(,new-vars (coerce-maxima-list ,maxima-new-vars)))))
807 (coerce-to-maxima
808 ,value-type
809 (with-coefficient-ring ($poly_coefficient_ring)
810 (with-monomial-order ($poly_monomial_order)
811 (with-elimination-orders ($poly_primary_elimination_order
812 $poly_secondary_elimination_order
813 $poly_elimination_order)
814 (let ,(let ((args nil))
815 (dolist (p polynomials args)
816 (setf args (cons `(,p (parse-poly ,p ,vars)) args)))
817 (dolist (p poly-lists args)
818 (setf args (cons `(,p (parse-poly-list ,p ,vars)) args)))
819 (dolist (p poly-list-lists args)
820 (setf args (cons `(,p (parse-poly-list-list ,p ,vars)) args))))
821 . ,body))))
822 ,(if new-vars-supplied-p
823 `(append ,vars ,new-vars)
824 vars))))
825
826(defmacro define-unop (maxima-name fun-name
827 &optional (documentation nil documentation-supplied-p))
828 "Define a MAXIMA-level unary operator MAXIMA-NAME corresponding to unary function FUN-NAME."
829 `(defun ,maxima-name (p vars
830 &aux
831 (vars (coerce-maxima-list vars))
832 (p (parse-poly p vars)))
833 ,@(when documentation-supplied-p (list documentation))
834 (coerce-to-maxima :polynomial (,fun-name *maxima-ring* p) vars)))
835
836(defmacro define-binop (maxima-name fun-name
837 &optional (documentation nil documentation-supplied-p))
838 "Define a MAXIMA-level binary operator MAXIMA-NAME corresponding to binary function FUN-NAME."
839 `(defmfun ,maxima-name (p q vars
840 &aux
841 (vars (coerce-maxima-list vars))
842 (p (parse-poly p vars))
843 (q (parse-poly q vars)))
844 ,@(when documentation-supplied-p (list documentation))
845 (coerce-to-maxima :polynomial (,fun-name *maxima-ring* p q) vars)))
846
847
848
849;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
850;;
851;; Maxima-level interface functions
852;;
853;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
854
855;; Auxillary function for removing zero polynomial
856(defun remzero (plist) (remove #'poly-zerop plist))
857
858;;Simple operators
859
860(define-binop $poly_add poly-add
861 "Adds two polynomials P and Q")
862
863(define-binop $poly_subtract poly-sub
864 "Subtracts a polynomial Q from P.")
865
866(define-binop $poly_multiply poly-mul
867 "Returns the product of polynomials P and Q.")
868
869(define-binop $poly_s_polynomial spoly
870 "Returns the syzygy polynomial (S-polynomial) of two polynomials P and Q.")
871
872(define-unop $poly_primitive_part poly-primitive-part
873 "Returns the polynomial P divided by GCD of its coefficients.")
874
875(define-unop $poly_normalize poly-normalize
876 "Returns the polynomial P divided by the leading coefficient.")
877
878;;Functions
879
880(defmfun $poly_expand (p vars)
881 "This function is equivalent to EXPAND(P) if P parses correctly to a polynomial.
882If the representation is not compatible with a polynomial in variables VARS,
883the result is an error."
884 (with-parsed-polynomials ((vars) :polynomials (p)
885 :value-type :polynomial)
886 p))
887
888(defmfun $poly_expt (p n vars)
889 (with-parsed-polynomials ((vars) :polynomials (p) :value-type :polynomial)
890 (poly-expt *maxima-ring* p n)))
891
892(defmfun $poly_content (p vars)
893 (with-parsed-polynomials ((vars) :polynomials (p))
894 (poly-content *maxima-ring* p)))
895
896(defmfun $poly_pseudo_divide (f fl vars
897 &aux (vars (coerce-maxima-list vars))
898 (f (parse-poly f vars))
899 (fl (parse-poly-list fl vars)))
900 (multiple-value-bind (quot rem c division-count)
901 (poly-pseudo-divide *maxima-ring* f fl)
902 `((mlist)
903 ,(coerce-to-maxima :poly-list quot vars)
904 ,(coerce-to-maxima :polynomial rem vars)
905 ,c
906 ,division-count)))
907
908(defmfun $poly_exact_divide (f g vars)
909 (with-parsed-polynomials ((vars) :polynomials (f g) :value-type :polynomial)
910 (poly-exact-divide *maxima-ring* f g)))
911
912(defmfun $poly_normal_form (f fl vars)
913 (with-parsed-polynomials ((vars) :polynomials (f)
914 :poly-lists (fl)
915 :value-type :polynomial)
916 (normal-form *maxima-ring* f (remzero fl) nil)))
917
918(defmfun $poly_buchberger_criterion (g vars)
919 (with-parsed-polynomials ((vars) :poly-lists (g) :value-type :logical)
920 (buchberger-criterion *maxima-ring* g)))
921
922(defmfun $poly_buchberger (fl vars)
923 (with-parsed-polynomials ((vars) :poly-lists (fl) :value-type :poly-list)
924 (buchberger *maxima-ring* (remzero fl) 0 nil)))
925
926(defmfun $poly_reduction (plist vars)
927 (with-parsed-polynomials ((vars) :poly-lists (plist)
928 :value-type :poly-list)
929 (reduction *maxima-ring* plist)))
930
931(defmfun $poly_minimization (plist vars)
932 (with-parsed-polynomials ((vars) :poly-lists (plist)
933 :value-type :poly-list)
934 (minimization plist)))
935
936(defmfun $poly_normalize_list (plist vars)
937 (with-parsed-polynomials ((vars) :poly-lists (plist)
938 :value-type :poly-list)
939 (poly-normalize-list *maxima-ring* plist)))
940
941(defmfun $poly_grobner (f vars)
942 (with-parsed-polynomials ((vars) :poly-lists (f)
943 :value-type :poly-list)
944 (grobner *maxima-ring* (remzero f))))
945
946(defmfun $poly_reduced_grobner (f vars)
947 (with-parsed-polynomials ((vars) :poly-lists (f)
948 :value-type :poly-list)
949 (reduced-grobner *maxima-ring* (remzero f))))
950
951(defmfun $poly_depends_p (p var mvars
952 &aux (vars (coerce-maxima-list mvars))
953 (pos (position var vars)))
954 (if (null pos)
955 (merror "~%Variable ~M not in the list of variables ~M." var mvars)
956 (poly-depends-p (parse-poly p vars) pos)))
957
958(defmfun $poly_elimination_ideal (flist k vars)
959 (with-parsed-polynomials ((vars) :poly-lists (flist)
960 :value-type :poly-list)
961 (elimination-ideal *maxima-ring* flist k nil 0)))
962
963(defmfun $poly_colon_ideal (f g vars)
964 (with-parsed-polynomials ((vars) :poly-lists (f g) :value-type :poly-list)
965 (colon-ideal *maxima-ring* f g nil)))
966
967(defmfun $poly_ideal_intersection (f g vars)
968 (with-parsed-polynomials ((vars) :poly-lists (f g) :value-type :poly-list)
969 (ideal-intersection *maxima-ring* f g nil)))
970
971(defmfun $poly_lcm (f g vars)
972 (with-parsed-polynomials ((vars) :polynomials (f g) :value-type :polynomial)
973 (poly-lcm *maxima-ring* f g)))
974
975(defmfun $poly_gcd (f g vars)
976 ($first ($divide (m* f g) ($poly_lcm f g vars))))
977
978(defmfun $poly_grobner_equal (g1 g2 vars)
979 (with-parsed-polynomials ((vars) :poly-lists (g1 g2))
980 (grobner-equal *maxima-ring* g1 g2)))
981
982(defmfun $poly_grobner_subsetp (g1 g2 vars)
983 (with-parsed-polynomials ((vars) :poly-lists (g1 g2))
984 (grobner-subsetp *maxima-ring* g1 g2)))
985
986(defmfun $poly_grobner_member (p g vars)
987 (with-parsed-polynomials ((vars) :polynomials (p) :poly-lists (g))
988 (grobner-member *maxima-ring* p g)))
989
990(defmfun $poly_ideal_saturation1 (f p vars)
991 (with-parsed-polynomials ((vars) :poly-lists (f) :polynomials (p)
992 :value-type :poly-list)
993 (ideal-saturation-1 *maxima-ring* f p 0)))
994
995(defmfun $poly_saturation_extension (f plist vars new-vars)
996 (with-parsed-polynomials ((vars new-vars)
997 :poly-lists (f plist)
998 :value-type :poly-list)
999 (saturation-extension *maxima-ring* f plist)))
1000
1001(defmfun $poly_polysaturation_extension (f plist vars new-vars)
1002 (with-parsed-polynomials ((vars new-vars)
1003 :poly-lists (f plist)
1004 :value-type :poly-list)
1005 (polysaturation-extension *maxima-ring* f plist)))
1006
1007(defmfun $poly_ideal_polysaturation1 (f plist vars)
1008 (with-parsed-polynomials ((vars) :poly-lists (f plist)
1009 :value-type :poly-list)
1010 (ideal-polysaturation-1 *maxima-ring* f plist 0 nil)))
1011
1012(defmfun $poly_ideal_saturation (f g vars)
1013 (with-parsed-polynomials ((vars) :poly-lists (f g)
1014 :value-type :poly-list)
1015 (ideal-saturation *maxima-ring* f g 0 nil)))
1016
1017(defmfun $poly_ideal_polysaturation (f ideal-list vars)
1018 (with-parsed-polynomials ((vars) :poly-lists (f)
1019 :poly-list-lists (ideal-list)
1020 :value-type :poly-list)
1021 (ideal-polysaturation *maxima-ring* f ideal-list 0 nil)))
1022
1023(defmfun $poly_lt (f vars)
1024 (with-parsed-polynomials ((vars) :polynomials (f) :value-type :polynomial)
1025 (make-poly-from-termlist (list (poly-lt f)))))
1026
1027(defmfun $poly_lm (f vars)
1028 (with-parsed-polynomials ((vars) :polynomials (f) :value-type :polynomial)
1029 (make-poly-from-termlist (list (make-term (poly-lm f) (funcall (ring-unit *maxima-ring*)))))))
1030
Note: See TracBrowser for help on using the repository browser.