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/polynomial.lisp@ 3254

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

* empty log message *

File size: 15.3 KB
Line 
1;;; -*- Mode: Lisp -*-
2;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
3;;;
4;;; Copyright (C) 1999, 2002, 2009, 2015 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(defpackage "POLYNOMIAL"
23 (:use :cl :utils :ring :monom :order :term)
24 (:export "POLY"
25 "POLY-TERMLIST"
26 "POLY-TERM-ORDER"
27 "CHANGE-TERM-ORDER"
28 "STANDARD-EXTENSION"
29 "STANDARD-EXTENSION-1"
30 "STANDARD-SUM"
31 "SATURATION-EXTENSION"
32 "ALIST->POLY")
33 (:documentation "Implements polynomials."))
34
35(in-package :polynomial)
36
37(proclaim '(optimize (speed 3) (space 0) (safety 0) (debug 0)))
38
39(defclass poly ()
40 ((dimension :initform nil
41 :initarg :dimension
42 :accessor poly-dimension
43 :documentation "Shared dimension of all terms, the number of variables")
44 (termlist :initform nil :initarg :termlist :accessor poly-termlist
45 :documentation "List of terms.")
46 (order :initform #'lex> :initarg :order :accessor poly-term-order
47 :documentation "Monomial/term order."))
48 (:default-initargs :dimension nil :termlist nil :order nil)
49 (:documentation "A polynomial with a list of terms TERMLIST, ordered
50according to term order ORDER, which defaults to LEX>."))
51
52(defmethod print-object ((self poly) stream)
53 (print-unreadable-object (self stream :type t :identity t)
54 (with-accessors ((dimension poly-dimension)
55 (termlist poly-termlist)
56 (order poly-term-order))
57 self
58 (format stream "DIMENSION=~A TERMLIST=~A ORDER=~A"
59 dimension termlist order))))
60
61(defgeneric change-term-order (self other)
62 (:documentation "Change term order of SELF to the term order of OTHER.")
63 (:method ((self poly) (other poly))
64 (unless (eq (poly-term-order self) (poly-term-order other))
65 (setf (poly-termlist self) (sort (poly-termlist self) (poly-term-order other))
66 (poly-term-order self) (poly-term-order other)))
67 self))
68
69(defun alist->poly (alist &aux (poly (make-instance 'poly)))
70 "It reads polynomial from an alist formatted as ( ... (exponents . coeff) ...).
71It can be used to enter simple polynomials by hand, e.g the polynomial
72in two variables, X and Y, given in standard notation as:
73
74 3*X^2*Y^3+2*Y+7
75
76can be entered as
77(ALIST->POLY '(((2 3) . 3) ((0 1) . 2) ((0 0) . 7))).
78
79NOTE: The primary use is for low-level debugging of the package."
80 (dolist (x alist poly)
81 (insert-item poly (make-instance 'term :exponents (car x) :coeff (cdr x)))))
82
83
84(defmethod r-equalp ((self poly) (other poly))
85 "POLY instances are R-EQUALP if they have the same
86order and if all terms are R-EQUALP."
87 (and (every #'r-equalp (poly-termlist self) (poly-termlist other))
88 (eq (poly-term-order self) (poly-term-order other))))
89
90(defmethod insert-item ((self poly) (item term))
91 (cond ((null (poly-dimension self))
92 (setf (poly-dimension self) (monom-dimension other)))
93 (t (assert (= (monom-dimension item) (poly-dimension self)))))
94 (push item (poly-termlist self))
95 self)
96
97(defmethod append-item ((self poly) (item term))
98 (cond ((null (poly-dimension self))
99 (setf (poly-dimension self) (monom-dimension other)))
100 (t (assert (= (monom-dimension item) (poly-dimension self)))))
101 (setf (cdr (last (poly-termlist self))) (list item))
102 self)
103
104;; Leading term
105(defgeneric leading-term (object)
106 (:method ((self poly))
107 (car (poly-termlist self)))
108 (:documentation "The leading term of a polynomial, or NIL for zero polynomial."))
109
110;; Second term
111(defgeneric second-leading-term (object)
112 (:method ((self poly))
113 (cadar (poly-termlist self)))
114 (:documentation "The second leading term of a polynomial, or NIL for a polynomial with at most one term."))
115
116;; Leading coefficient
117(defgeneric leading-coefficient (object)
118 (:method ((self poly))
119 (scalar-coeff (leading-term self)))
120 (:documentation "The leading coefficient of a polynomial. It signals error for a zero polynomial."))
121
122;; Second coefficient
123(defgeneric second-leading-coefficient (object)
124 (:method ((self poly))
125 (scalar-coeff (second-leading-term self)))
126 (:documentation "The second leading coefficient of a polynomial. It
127 signals error for a polynomial with at most one term."))
128
129;; Testing for a zero polynomial
130(defmethod r-zerop ((self poly))
131 (null (poly-termlist self)))
132
133;; The number of terms
134(defmethod r-length ((self poly))
135 (length (poly-termlist self)))
136
137(defmethod multiply-by ((self poly) (other monom))
138 (assert (= (monom-dimension self) (poly-dimension other)))
139 (mapc #'(lambda (term) (multiply-by term other))
140 (poly-termlist self))
141 self)
142
143(defmethod multiply-by ((self poly) (other term))
144 (assert (= (monom-dimension self) (monom-dimension other)))
145 (mapc #'(lambda (term) (multiply-by term other))
146 (poly-termlist self))
147 self)
148
149(defmethod multiply-by ((self poly) (other scalar))
150 (assert (= (monom-dimension self) (monom-dimension other)))
151 (mapc #'(lambda (term) (multiply-by term other))
152 (poly-termlist self))
153 self)
154
155
156(defmacro fast-add/subtract (p q order-fn add/subtract-fn uminus-fn)
157 "Return an expression which will efficiently adds/subtracts two
158polynomials, P and Q. The addition/subtraction of coefficients is
159performed by calling ADD/SUBTRACT-METHOD-NAME. If UMINUS-METHOD-NAME
160is supplied, it is used to negate the coefficients of Q which do not
161have a corresponding coefficient in P. The code implements an
162efficient algorithm to add two polynomials represented as sorted lists
163of terms. The code destroys both arguments, reusing the terms to build
164the result."
165 `(macrolet ((lc (x) `(scalar-coeff (car ,x))))
166 (do ((p ,p)
167 (q ,q)
168 r)
169 ((or (endp p) (endp q))
170 ;; NOTE: R contains the result in reverse order. Can it
171 ;; be more efficient to produce the terms in correct order?
172 (unless (endp q)
173 ;; Upon subtraction, we must change the sign of
174 ;; all coefficients in q
175 ,@(when uminus-fn
176 `((mapc #'(lambda (x) (setf x (funcall ,uminus-fn x))) q)))
177 (setf r (nreconc r q)))
178 r)
179 (multiple-value-bind
180 (greater-p equal-p)
181 (funcall ,order-fn (car p) (car q))
182 (cond
183 (greater-p
184 (rotatef (cdr p) r p)
185 )
186 (equal-p
187 (let ((s (funcall ,add/subtract-fn (lc p) (lc q))))
188 (cond
189 ((r-zerop s)
190 (setf p (cdr p))
191 )
192 (t
193 (setf (lc p) s)
194 (rotatef (cdr p) r p))))
195 (setf q (cdr q))
196 )
197 (t
198 ;;Negate the term of Q if UMINUS provided, signallig
199 ;;that we are doing subtraction
200 ,(when uminus-fn
201 `(setf (lc q) (funcall ,uminus-fn (lc q))))
202 (rotatef (cdr q) r q)))))))
203
204
205(defmacro def-add/subtract-method (add/subtract-method-name
206 uminus-method-name
207 &optional
208 (doc-string nil doc-string-supplied-p))
209 "This macro avoids code duplication for two similar operations: ADD-TO and SUBTRACT-FROM."
210 `(defmethod ,add/subtract-method-name ((self poly) (other poly))
211 ,@(when doc-string-supplied-p `(,doc-string))
212 ;; Ensure orders are compatible
213 (change-term-order other self)
214 (setf (poly-termlist self) (fast-add/subtract
215 (poly-termlist self) (poly-termlist other)
216 (poly-term-order self)
217 #',add/subtract-method-name
218 ,(when uminus-method-name `(function ,uminus-method-name))))
219 self))
220
221(eval-when (:compile-toplevel :load-toplevel :execute)
222
223 (def-add/subtract-method add-to nil
224 "Adds to polynomial SELF another polynomial OTHER.
225This operation destructively modifies both polynomials.
226The result is stored in SELF. This implementation does
227no consing, entirely reusing the sells of SELF and OTHER.")
228
229 (def-add/subtract-method subtract-from unary-minus
230 "Subtracts from polynomial SELF another polynomial OTHER.
231This operation destructively modifies both polynomials.
232The result is stored in SELF. This implementation does
233no consing, entirely reusing the sells of SELF and OTHER.")
234 )
235
236(defmethod unary-minus ((self poly))
237 "Destructively modifies the coefficients of the polynomial SELF,
238by changing their sign."
239 (mapc #'unary-minus (poly-termlist self))
240 self)
241
242(defun add-termlists (p q order-fn)
243 "Destructively adds two termlists P and Q ordered according to ORDER-FN."
244 (fast-add/subtract p q order-fn #'add-to nil))
245
246(defmacro multiply-term-by-termlist-dropping-zeros (term termlist
247 &optional (reverse-arg-order-P nil))
248 "Multiplies term TERM by a list of term, TERMLIST.
249Takes into accound divisors of zero in the ring, by
250deleting zero terms. Optionally, if REVERSE-ARG-ORDER-P
251is T, change the order of arguments; this may be important
252if we extend the package to non-commutative rings."
253 `(mapcan #'(lambda (other-term)
254 (let ((prod (r*
255 ,@(cond
256 (reverse-arg-order-p
257 `(other-term ,term))
258 (t
259 `(,term other-term))))))
260 (cond
261 ((r-zerop prod) nil)
262 (t (list prod)))))
263 ,termlist))
264
265(defun multiply-termlists (p q order-fn)
266 "A version of polynomial multiplication, operating
267directly on termlists."
268 (cond
269 ((or (endp p) (endp q))
270 ;;p or q is 0 (represented by NIL)
271 nil)
272 ;; If p= p0+p1 and q=q0+q1 then p*q=p0*q0+p0*q1+p1*q
273 ((endp (cdr p))
274 (multiply-term-by-termlist-dropping-zeros (car p) q))
275 ((endp (cdr q))
276 (multiply-term-by-termlist-dropping-zeros (car q) p t))
277 (t
278 (cons (r* (car p) (car q))
279 (add-termlists
280 (multiply-term-by-termlist-dropping-zeros (car p) (cdr q))
281 (multiply-termlists (cdr p) q order-fn)
282 order-fn)))))
283
284(defmethod multiply-by ((self poly) (other poly))
285 (assert (= (monom-dimension self) (monom-dimension other)))
286 (change-term-order other self)
287 (setf (poly-termlist self) (multiply-termlists (poly-termlist self)
288 (poly-termlist other)
289 (poly-term-order self)))
290 self)
291
292(defmethod r* ((poly1 poly) (poly2 poly))
293 "Non-destructively multiply POLY1 by POLY2."
294 (multiply-by (copy-instance POLY1) (copy-instance POLY2)))
295
296(defmethod left-tensor-product-by ((self poly) (other term))
297 (setf (poly-termlist self)
298 (mapcan #'(lambda (term)
299 (let ((prod (left-tensor-product-by term other)))
300 (cond
301 ((r-zerop prod) nil)
302 (t (list prod)))))
303 (poly-termlist self)))
304 self)
305
306(defmethod right-tensor-product-by ((self poly) (other term))
307 (setf (poly-termlist self)
308 (mapcan #'(lambda (term)
309 (let ((prod (right-tensor-product-by term other)))
310 (cond
311 ((r-zerop prod) nil)
312 (t (list prod)))))
313 (poly-termlist self)))
314 self)
315
316(defmethod left-tensor-product-by ((self poly) (other monom))
317 (setf (poly-termlist self)
318 (mapcan #'(lambda (term)
319 (let ((prod (left-tensor-product-by term other)))
320 (cond
321 ((r-zerop prod) nil)
322 (t (list prod)))))
323 (poly-termlist self)))
324 (incf (poly-dimension self) (monom-dimension other))
325 self)
326
327(defmethod right-tensor-product-by ((self poly) (other monom))
328 (setf (poly-termlist self)
329 (mapcan #'(lambda (term)
330 (let ((prod (right-tensor-product-by term other)))
331 (cond
332 ((r-zerop prod) nil)
333 (t (list prod)))))
334 (poly-termlist self)))
335 (incf (poly-dimension self) (monom-dimension other))
336 self)
337
338
339(defun standard-extension (plist &aux (k (length plist)) (i 0))
340 "Calculate [U1*P1,U2*P2,...,UK*PK], where PLIST=[P1,P2,...,PK]
341is a list of polynomials. Destructively modifies PLIST elements."
342 (mapc #'(lambda (poly)
343 (left-tensor-product-by
344 poly
345 (prog1
346 (make-monom-variable k i)
347 (incf i))))
348 plist))
349
350(defun standard-extension-1 (plist
351 &aux
352 (plist (standard-extension plist))
353 (nvars (poly-dimension (car plist))))
354 "Calculate [U1*P1-1,U2*P2-1,...,UK*PK-1], where PLIST=[P1,P2,...,PK].
355Firstly, new K variables U1, U2, ..., UK, are inserted into each
356polynomial. Subsequently, P1, P2, ..., PK are destructively modified
357tantamount to replacing PI with UI*PI-1. It assumes that all
358polynomials have the same dimension, and only the first polynomial
359is examined to determine this dimension."
360 ;; Implementation note: we use STANDARD-EXTENSION and then subtract
361 ;; 1 from each polynomial; since UI*PI has no constant term,
362 ;; we just need to append the constant term at the end
363 ;; of each termlist.
364 (flet ((subtract-1 (p)
365 (append-item p (make-instance 'term :coeff -1 :dimension nvars))))
366 (setf plist (mapc #'subtract-1 plist)))
367 plist)
368
369
370(defun standard-sum (plist
371 &aux
372 (plist (standard-extension plist))
373 (nvars (poly-dimension (car plist))))
374 "Calculate the polynomial U1*P1+U2*P2+...+UK*PK-1, where PLIST=[P1,P2,...,PK].
375Firstly, new K variables, U1, U2, ..., UK, are inserted into each
376polynomial. Subsequently, P1, P2, ..., PK are destructively modified
377tantamount to replacing PI with UI*PI, and the resulting polynomials
378are added. Finally, 1 is subtracted. It should be noted that the term
379order is not modified, which is equivalent to using a lexicographic
380order on the first K variables."
381 (flet ((subtract-1 (p)
382 (append-item p (make-instance 'term :coeff -1 :dimension nvars))))
383 (subtract-1
384 (make-instance
385 'poly
386 :termlist (apply #'nconc (mapcar #'poly-termlist plist))))))
387
388#|
389
390(defun saturation-extension-1 (ring f p)
391 "Calculate [F, U*P-1]. It destructively modifies F."
392 (declare (type ring ring))
393 (polysaturation-extension ring f (list p)))
394
395
396
397
398(defun spoly (ring-and-order f g
399 &aux
400 (ring (ro-ring ring-and-order)))
401 "It yields the S-polynomial of polynomials F and G."
402 (declare (type ring-and-order ring-and-order) (type poly f g))
403 (let* ((lcm (monom-lcm (poly-lm f) (poly-lm g)))
404 (mf (monom-div lcm (poly-lm f)))
405 (mg (monom-div lcm (poly-lm g))))
406 (declare (type monom mf mg))
407 (multiple-value-bind (c cf cg)
408 (funcall (ring-ezgcd ring) (poly-lc f) (poly-lc g))
409 (declare (ignore c))
410 (poly-sub
411 ring-and-order
412 (scalar-times-poly ring cg (monom-times-poly mf f))
413 (scalar-times-poly ring cf (monom-times-poly mg g))))))
414
415
416(defun poly-primitive-part (ring p)
417 "Divide polynomial P with integer coefficients by gcd of its
418coefficients and return the result."
419 (declare (type ring ring) (type poly p))
420 (if (poly-zerop p)
421 (values p 1)
422 (let ((c (poly-content ring p)))
423 (values (make-poly-from-termlist
424 (mapcar
425 #'(lambda (x)
426 (make-term :monom (term-monom x)
427 :coeff (funcall (ring-div ring) (term-coeff x) c)))
428 (poly-termlist p))
429 (poly-sugar p))
430 c))))
431
432(defun poly-content (ring p)
433 "Greatest common divisor of the coefficients of the polynomial P. Use the RING structure
434to compute the greatest common divisor."
435 (declare (type ring ring) (type poly p))
436 (reduce (ring-gcd ring) (mapcar #'term-coeff (rest (poly-termlist p))) :initial-value (poly-lc p)))
437
438|#
Note: See TracBrowser for help on using the repository browser.