source: CGBLisp/trunk/src/grobner.lisp@ 14

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

Moving sources to trunk

File size: 67.0 KB
Line 
1;;; -*- Mode: Lisp; Syntax: Common-Lisp; Package: Grobner; Base: 10 -*-
2#|
3 $Id: grobner.lisp,v 1.8 2009/01/23 10:40:26 marek Exp $
4 *--------------------------------------------------------------------------*
5 | Copyright (C) 1994, Marek Rychlik (e-mail: rychlik@math.arizona.edu) |
6 | Department of Mathematics, University of Arizona, Tucson, AZ 85721 |
7 | |
8 | Everyone is permitted to copy, distribute and modify the code in this |
9 | directory, as long as this copyright note is preserved verbatim. |
10 *--------------------------------------------------------------------------*
11|#
12(defpackage "GROBNER"
13 (:use "ORDER" "PARSE" "PRINTER" "DIVISION" "MONOM"
14 "MAKELIST" "COEFFICIENT-RING" "TERM" "POLY"
15 "POLY-WITH-SUGAR" "COMMON-LISP")
16 (:export
17 spoly
18 grobner
19 reduction
20 normal-form
21 reduced-grobner
22 normalize-poly
23 normalize-basis
24 elimination-ideal
25 ring-intersection
26 poly-contract
27 ideal-intersection
28 poly-lcm
29 grobner-gcd
30 pseudo-divide
31 buchberger-criterion
32 grobner-test
33 grobner-equal
34 grobner-subsetp
35 grobner-member
36 ideal-equal
37 ideal-subsetp
38 ideal-member
39 ideal-saturation
40 ideal-polysaturation
41 ideal-saturation-1
42 ideal-polysaturation-1
43 grobner-primitive-part
44 grobner-content
45 colon-ideal
46 *grobner-debug*
47 buchberger-set-pair-heuristic
48 gebauer-moeller-set-pair-heuristic
49 select-grobner-algorithm
50 spoly-with-sugar
51 normal-form-with-sugar
52 grobner-with-sugar
53 ))
54
55(in-package "GROBNER")
56
57(proclaim '(optimize (speed 0) (debug 3)))
58
59#+debug
60(defvar *grobner-debug* nil
61 "If T, produce debugging and tracing output.")
62
63(defvar *buchberger-merge-pairs* 'buchberger-merge-pairs-smallest-lcm
64 "A variable holding the predicate used to sort critical pairs
65in the order of decreasing priority for the Buchberger algorithm.")
66
67(defvar *gebauer-moeller-merge-pairs* 'gebauer-moeller-merge-pairs-use-mock-spoly
68 "A variable holding the predicate used to sort critical pairs
69in the order of decreasing priority for the Gebauer-Moeller algorithm")
70
71(defvar *grobner-function* 'buchberger
72 "The name of the function used to calculate Grobner basis")
73
74(defun select-grobner-algorithm (algorithm)
75 "Select one of the several implementations of the Grobner basis
76algorithm."
77 (setf *grobner-function*
78 (ecase algorithm
79 (:buchberger 'buchberger)
80 (:cached-buchberger 'cached-buchberger)
81 (:gebauer-moeller 'gebauer-moeller)
82 (:sugar 'buchberger-with-sugar)
83 (:cached-sugar 'cached-buchberger-with-sugar)
84 (:gebauer-moeller-with-sugar 'gebauer-moeller-with-sugar))))
85
86(defun grobner (F &optional (pred #'lex>)
87 (start 0)
88 (top-reduction-only nil)
89 (ring *coefficient-ring*))
90 "Return Grobner basis of an ideal generated by polynomial list F.
91Assume that the monomials of each polynomial are ordered according to
92the admissible monomial order PRED. The result will be a list of
93polynomials ordered as well according to PRED. The polynomials from 0
94to START-1 in the list F are assumed to be a Grobner basis, and thus
95certain critical pairs do not have to be calculated. If
96TOP-REDUCTION-ONLY is not NIL then only top reductions will be
97performed, instead of full division, and thus the returned Grobner
98basis will have its polynomials only top-reduced with respect to the
99preceding polynomials. RING should be set to the RING structure (see
100COEFFICIENT-RING package) corresponding to the coefficients of the
101polynomials in the list F. This function is currently just an
102interface to several algorithms which fine Grobner bases. Use
103SELECT-GROBNER-ALGORITHM in order to change the algorithm."
104 (funcall *grobner-function* F pred start top-reduction-only ring))
105
106
107#+debug
108(defmacro debug-cgb (&rest args)
109 "This macro is used in printing debugging and tracing messages
110and its arguments are analogous to the FORMAT function, except
111that the stream argument is omitted. By default, the output is
112sent to *trace-output*, which can be set to produce output
113in a file."
114 `(when *grobner-debug* (format *trace-output* ,@args)))
115
116(defun spoly (f g pred ring)
117 "Return the S-polynomial of F and G, which should
118be two polynomials with terms ordered by PRED and
119coefficients in a ring whose operations are the slots
120of the RING structure."
121 (declare (optimize (speed 3) (safety 0)))
122 (let* ((lcm (monom-lcm (lm f) (lm g)))
123 (m1 (monom/ lcm (lm f)))
124 (m2 (monom/ lcm (lm g))))
125 (let* ((c (funcall (ring-lcm ring) (lc f) (lc g)))
126 (cf (funcall (ring-/ ring) c (lc f)))
127 (cg (funcall (ring-/ ring) c (lc g))))
128 (poly-
129 (term-times-poly (cons m1 cf) (rest f) ring)
130 (term-times-poly (cons m2 cg) (rest g) ring)
131 pred
132 ring))))
133
134
135(defun grobner-primitive-part (p ring)
136 "Divide polynomial P with integer coefficients by gcd of its
137coefficients and return the result. Use the RING structure from the
138COEFFICIENT-RING package to perform the operations on the
139coefficients."
140 (if (poly-zerop p)
141 (values p 1)
142 (let ((c (grobner-content p ring)))
143 (values (mapcar
144 #'(lambda (x)
145 (cons (car x)
146 (funcall
147 (ring-/ ring)
148 (cdr x) c)))
149 p)
150 c))))
151
152
153(defun grobner-content (p ring)
154 "Greatest common divisor of the coefficients of the polynomial P. Use the RING structure
155to compute the greatest common divisor."
156 (let ((c (apply (ring-gcd ring) (mapcar #'cdr p))))
157 (when (/= (funcall (ring-signum ring) (cdar p))
158 (funcall (ring-signum ring) c))
159 (setf c (funcall (ring-- ring) c)))
160 c))
161
162(defun normal-form (f fl pred top-reduction-only ring)
163 "Calculate the normal form of the polynomial F with respect to
164the polynomial list FL. Destructive to F; thus, copy-tree should be used
165where F needs to be preserved. It returns multiple values.
166The first value is the polynomial R which is reduced (or top-reduced
167if TOP-REDUCTION-ONLY is not NIL). The second value is an integer
168which is the number of reductions actually performed. The third value
169is the coefficient by which F needs to be multiplied in order to be
170able to perform the division without actually having to divide in the
171coefficient ring (a form of pseudo-division is used). All operations
172on the coefficients are performed using the RING structure from the
173COEFFICIENT-RING package."
174 (declare (optimize (speed 3) (safety 0)))
175 ;; Loop invariant: c*f=sum ai*fi+r+p
176 (do (r (c (ring-unit ring))
177 (division-count 0)
178 (p f))
179 ((or (endp p)
180 (endp fl)
181 (and top-reduction-only r))
182 #+debug(progn
183 (debug-cgb "~&~3T~d reduction~:p" division-count)
184 (when (endp r)
185 (debug-cgb " ---> 0")))
186 (values (append (nreverse r) p)
187 division-count c))
188 (declare (fixnum division-count) (integer c))
189 (let ((g (find (lm p) fl :test #'monom-divisible-by-p :key #'lm)))
190 (cond
191 (g ;division possible
192 (incf division-count)
193 (let* ((gcd (funcall (ring-gcd ring) (lc g) (lc p)))
194 (c1 (funcall (ring-/ ring) (lc g) gcd))
195 (c2 (funcall (ring-/ ring) (lc p) gcd))
196 (m (monom/ (lm p) (lm g))))
197 ;; Multiply the equation c*f=sum ai*fi+r+p by c1.
198 (setf r (scalar-times-poly c1 r ring)
199 c (funcall (ring-* ring) c c1)
200 p (grobner-op c2 c1 m (rest p) (rest g) pred ring))))
201 (t ;no division possible
202 (setf r (cons (lt p) r) ;move lt(p) to remainder
203 p (rest p))))))) ;remove lt(p) from p
204
205(defun buchberger (F pred start top-reduction-only ring
206 &aux (s (1- (length F))) B M)
207 "An implementation of the Buchberger algorithm. Return Grobner
208basis of the ideal generated by the polynomial list F.
209The terms of each polynomial are ordered by the admissible
210monomial order PRED. Polynomials 0 to START-1 are assumed to
211be a Grobner basis already, so that certain critical pairs
212will not be examined. If TOP-REDUCTION-ONLY set, top reduction
213will be preformed. The RING structure is used to perform operations
214on coefficents (see COEFFICIENT-RING package)."
215 (declare (fixnum s))
216 (unless (plusp s) (return-from buchberger F)) ;cut startup costs
217 #+debug (debug-cgb "~&GROBNER BASIS - BUCHBERGER ALGORITHM")
218 #+debug (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
219 #+grobner-check (when (plusp start)
220 (grobner-test (subseq F 0 start) (subseq F 0 start) pred ring))
221 (setf B (nconc (makelist (list i j) (i 0 (1- start)) (j start s))
222 (makelist (list i j) (i start (1- s)) (j (1+ i) s)))
223 M (make-hash-table :test #'equal)
224 B (buchberger-sort-pairs B F pred ring))
225 ;;Initialize treated pairs
226 (dotimes (i (1- start))
227 (do ((j (1+ i) (1+ j))) ((>= j start))
228 (setf (gethash (list i j) M) t)))
229 (do ((G F))
230 ((endp B)
231 #+grobner-check(grobner-test G F pred ring)
232 #+debug(debug-cgb "~&GROBNER END")
233 G)
234 (let ((pair (pop B)))
235 (unless (or (Criterion-1 pair G)
236 (Criterion-2 pair G M))
237 (let ((SP (normal-form (spoly (elt G (first pair))
238 (elt G (second pair))
239 pred
240 ring)
241 G pred top-reduction-only ring)))
242 (unless (poly-zerop SP) ;S-polynomial ---> 0;
243 (setf s (1+ s)
244 SP (grobner-primitive-part SP ring)
245 G (nconc G (list SP))
246 B (funcall *buchberger-merge-pairs* B (makelist (list i s)
247 (i 0 (1- s)))
248 G pred ring))
249 #+debug (debug-cgb "~&Polynomials: ~d; Pairs left: ~d; Treated pairs: ~d"
250 (length G) (length B)
251 (hash-table-count M)))))
252 (setf (gethash pair M) t))))
253
254(defun grobner-op (c1 c2 m A B pred ring &aux n A1 A2)
255 "Perform a calculation equivalent to
256(POLY- (SCALAR-TIMES-POLY C2 A)
257 (SCALAR-TIMES-POLY C1 (MONOM-TIMES-POLY M B))
258 PRED)
259but more efficiently; it destructively modifies A and stores the
260result in it; A is returned."
261 (dolist (x A) (setf (cdr x) (funcall (ring-* ring) c2 (cdr x))))
262 (unless B
263 (return-from grobner-op A))
264 (unless A
265 (return-from grobner-op
266 (mapcar
267 #'(lambda (x) (cons (monom* m (car x))
268 (funcall (ring-- ring)
269 (funcall (ring-* ring)
270 c1 (cdr x)))))
271 B)))
272 (setf A1 (cons nil A) A2 A1)
273 (tagbody
274 begin-outer-loop
275 (unless B
276 (return-from grobner-op (cdr A2)))
277 (setf n (monom* m (caar B)))
278 (tagbody
279 begin-inner-loop
280 (unless (cdr A1)
281 (setf (cdr A1)
282 (mapcar #'(lambda (x) (cons (monom* m (car x))
283 (funcall (ring-- ring)
284 (funcall (ring-* ring)
285 c1 (cdr x))))) B))
286 (return-from grobner-op (cdr A2)))
287 (multiple-value-bind (lm-greater lm-equal)
288 (funcall pred (caadr A1) n)
289 (cond
290 (lm-equal
291 (let ((s (funcall (ring-- ring)
292 (cdadr A1)
293 (funcall (ring-* ring) c1 (cdar B)))))
294 (if (funcall (ring-zerop ring) s) ;check for cancellation
295 (setf (cdr A1) (cddr A1))
296 (setf (cdadr A1) s))
297 (setf B (cdr B))
298 (go begin-outer-loop)))
299 (lm-greater
300 (setf A1 (cdr A1))
301 (go begin-inner-loop))
302 (t ;(lm B) is greater than (lm A)
303 (setf (cdr A1)
304 (cons
305 (cons
306 n
307 (funcall (ring-- ring)
308 (funcall (ring-* ring) c1 (cdar B))))
309 (cdr A1))
310 B (cdr B)
311 A1 (cdr A1))
312 (go begin-outer-loop)))))))
313
314;;----------------------------------------------------------------
315;; Pairs
316;;----------------------------------------------------------------
317
318(defun buchberger-sort-pairs (B G pred ring)
319 "Sort critical pairs B by the function which is
320the value of the vairable *buchberger-merge-pairs*.
321G is the list of polynomials which the elemnts
322of B point into. PRED is the admissible monomial order.
323The RING structure holds operations on the coefficients
324as described in the COEFFICIENT-RING package."
325 (funcall *buchberger-merge-pairs* nil B G pred ring))
326
327
328(defun mock-spoly (f g pred)
329 "Returns an upper-bound on the leading
330monomial of the S-polynomial of F and G, which are two polynomials
331sorted by the admissible monomial order PRED."
332 (let* ((lcm (monom-lcm (lm f) (lm g)))
333 (m1 (monom/ lcm (lm f)))
334 (m2 (monom/ lcm (lm g))))
335 (cond
336 ((endp (second f))
337 (monom* m2 (car (second g))))
338 ((endp (second g))
339 (monom* m1 (car (second f))))
340 (t (let ((n1 (monom* m2 (car (second g))))
341 (n2 (monom* m1 (car (second f)))))
342 (if (funcall pred n1 n2)
343 n1
344 n2))))))
345
346;;----------------------------------------------------------------
347;; A stragegy based on a predicted approximate S-polynomials
348;;----------------------------------------------------------------
349(defun buchberger-merge-pairs-use-mock-spoly (B C G pred ring)
350 "Merges lists of critical pairs B and C into one list.
351The pairs are assumed to be ordered according to the
352increasing value of MOCK-SPOLY, as determined by the admissible
353monomial order PRED. G is the list of polynomials which the pairs
354of integers in B and C point into, and RING is the ring structure
355defined in the COEFFICIENT-RING package."
356 (declare (ignore ring))
357 ;; Delete pairs consisting of two single monomials
358 (setf C (delete-if
359 #'(lambda (p) (and (endp (cdr (elt G (first p))))
360 (endp (cdr (elt G (second p))))))
361 C))
362 (labels ((pair-key (p) (mock-spoly (elt G (first p))
363 (elt G (second p)) pred))
364 (pair-order (x y) (funcall pred y x)))
365 (merge 'list B (sort C #'pair-order :key #'pair-key)
366 #'pair-order :key #'pair-key)))
367
368
369;;----------------------------------------------------------------
370;; A strategy based on the smallest lcm of the leading
371;; monomials of the two polynomials - so called normal strategy
372;;----------------------------------------------------------------
373(defun buchberger-merge-pairs-smallest-lcm (B C G pred ring)
374 "Merges lists of critical pairs B and C into a single ordered
375list. Implements a strategy of ordering pairs according to the
376smallest lcm of the leading monomials of the two polynomials - so
377called normal strategy."
378 (declare (ignore ring))
379 (labels ((pair-key (p) (monom-lcm (lm (elt G (first p)))
380 (lm (elt G (second p)))))
381 (pair-order (x y) (funcall pred y x)))
382 (merge 'list B (sort C #'pair-order :key #'pair-key)
383 #'pair-order :key #'pair-key)))
384
385;;----------------------------------------------------------------
386;; A strategy based on the smallest degree of the lcm of the leading
387;; monomials of the two polynomials
388;;----------------------------------------------------------------
389(defun buchberger-merge-pairs-use-smallest-degree (B C G pred ring)
390 "Mergest lists B and C of critical pairs. This strategy is based on
391 ordering the pairs according to the smallest degree of the lcm of the
392 leading monomials of the two polynomials."
393 (declare (ignore pred ring))
394 (labels ((pair-key (p) (total-degree
395 (monom-lcm (lm (elt G (first p)))
396 (lm (elt G (second p)))))))
397 (merge 'list B (sort C #'< :key #'pair-key) #'< :key #'pair-key)))
398
399(defun buchberger-merge-pairs-use-smallest-length (B C G pred ring)
400 "Mergest lists B and C of critical pairs. This strategy is based on
401 ordering the pairs according to the smallest total length of the
402 two polynomials, where length is the number of terms."
403 (declare (ignore pred ring))
404 (labels ((pair-key (p) (+
405 (length (elt G (first p)))
406 (length (elt G (second p))))))
407 (merge 'list B (sort C #'< :key #'pair-key) #'< :key #'pair-key)))
408
409(defun buchberger-merge-pairs-use-smallest-coefficient-length (B C G pred ring)
410 "Mergest lists B and C of critical pairs. This strategy is based on
411 ordering the pairs according to the smallest combined length of the
412 coefficients of the two polynomials."
413 (declare (ignore pred))
414 (labels ((coefficient-length (poly)
415 (apply #'+ (mapcar (ring-length ring)
416 (mapcar #'cdr poly))))
417 (pair-key (p) (+
418 (coefficient-length (elt G (first p)))
419 (coefficient-length (elt G (second p))))))
420 (merge 'list B (sort C #'< :key #'pair-key) #'< :key #'pair-key)))
421
422(defun buchberger-set-pair-heuristic
423 (method
424 &aux
425 (strategy-fn
426 (ecase method
427 (:minimal-mock-spoly #'buchberger-merge-pairs-use-mock-spoly)
428 (:minimal-lcm #'buchberger-merge-pairs-smallest-lcm)
429 (:minimal-total-degree #'buchberger-merge-pairs-use-smallest-degree)
430 (:minimal-length #'buchberger-merge-pairs-use-smallest-length)
431 (:minimal-coefficient-length #'buchberger-merge-pairs-use-smallest-coefficient-length))))
432 "Simply sets the variable *buchberger-merge-pairs* to the heuristic
433function STRATEGY-FN implementing one of several strategies introduces
434before of selecting the most promising. METHOD should be one of the
435listed keywords."
436 (setf *buchberger-merge-pairs* strategy-fn))
437
438;;----------------------------------------------------------------
439;; Grobner Criteria
440;;----------------------------------------------------------------
441(defun Criterion-1 (pair G &aux (i (first pair)) (j (second pair)))
442 "Returns T if the leading monomials of the two polynomials
443in G pointed to by the integers in PAIR have disjoint (relatively prime)
444monomials. This test is known as the first Buchberger criterion."
445 (monom-rel-prime (lm (elt G i))
446 (lm (elt G j))))
447
448
449(defun Criterion-2 (pair G M &aux (i (first pair)) (j (second pair)))
450 "Returns T if the leading monomial of some element P of G divides
451the LCM of the leading monomials of the two polynomials in the
452polynomial list G, pointed to by the two integers in PAIR, and P
453paired with each of the polynomials pointed to by the the PAIR has
454already been treated, as indicated by the hash table M, which stores
455value T for every treated pair so far."
456 (labels ((make-pair (u v) (if (< u v) (list u v) (list v u))))
457 (dotimes (k (length G) nil)
458 (when (and (/= k i)
459 (/= k j)
460 (monom-divides-p
461 (lm (elt G k))
462 (monom-lcm (lm (elt G i)) (lm (elt G j))))
463 (gethash (make-pair i k) M)
464 (gethash (make-pair k j) M))
465 #+debug(when *grobner-debug* (format t ":B2"))
466 (return-from Criterion-2 t)))))
467
468;;----------------------------------------------------------------
469;; End of GROBNER implementation
470;;----------------------------------------------------------------
471
472(defun normalize-poly (p ring)
473 "Divide a polynomial by its leading coefficient. It assumes
474that the division is possible, which may not always be the
475case in rings which are not fields. The exact division operator
476is assumed to be provided by the RING structure of the
477COEFFICIENT-RING package."
478 (mapcar #'(lambda (term)
479 (cons
480 (car term)
481 (funcall (ring-/ ring) (cdr term) (lc p)))) p))
482
483(defun normalize-basis (plist ring)
484 "Divide every polynomial in a list PLIST by its leading coefficient.
485Use RING structure to perform the division of the coefficients."
486 (mapcar #'(lambda (x) (normalize-poly x ring)) plist))
487
488(defun reduction (P pred ring)
489 "Reduce a list of polynomials P, so that non of the terms in any of the
490polynomials is divisible by a leading monomial of another polynomial.
491Return the reduced list."
492 (do ((Q P)
493 (found t))
494 ((not found)
495 (mapcar #'(lambda (x) (grobner-primitive-part x ring)) Q))
496 ;;Find p in Q such that p is reducible mod Q\{p}
497 (setf found nil)
498 (dolist (x Q)
499 (let ((Q1 (remove x Q)))
500 (multiple-value-bind (h div-count)
501 (normal-form x Q1
502 pred
503 nil ;not a top reduction
504 ring)
505 (unless (zerop div-count)
506 (setf found t Q Q1)
507 (when h
508 (setf Q (nconc Q1 (list h))))
509 (return)))))))
510
511
512(defun reduced-grobner (F &optional (pred #'lex>)
513 (start 0)
514 (top-reduction-only nil)
515 (ring *coefficient-ring*))
516 "Return the reduced Grobner basis of the ideal generated by a polynomial
517list F. This combines calls to two functions: GROBNER and REDUCTION.
518The parameters have the same meaning as in GROBNER or BUCHBERGER."
519 (reduction (grobner F pred start top-reduction-only ring) pred ring))
520
521#+kcl
522(defvar *vars* nil "Keep track of variables for tracing SPOLY.")
523
524;; Does the monomial P depend on variable K
525(defun monom-depends-p (m k)
526 "Return T if the monomial M depends on variable number K."
527 (plusp (elt m k)))
528
529;; Does the term depend on variable K
530(defun term-depends-p (term k)
531 "Return T if the term TERM depends on variable number K."
532 (monom-depends-p (car term) k))
533
534;; Does the polynomial P depend on variable K
535(defun poly-depends-p (p k)
536 "Return T if the term polynomial P depends on variable number K."
537 (some #'(lambda (term) (term-depends-p term k)) p))
538
539(defun ring-intersection (plist k &key (key #'identity))
540 "This function assumes that polynomial list PLIST is a Grobner basis
541and it calculates the intersection with the ring R[x[k+1],...,x[n]], i.e.
542it discards polynomials which depend on variables x[0], x[1], ..., x[k]."
543 (dotimes (i k plist)
544 (setf plist
545 (remove-if #'(lambda (p)
546 (poly-depends-p p (funcall key i)))
547 plist))))
548
549(defun elimination-ideal (flist k
550 &key
551 (primary-order #'lex>)
552 (secondary-order #'lex>)
553 (start 0)
554 (order (elimination-order
555 k
556 :primary-order primary-order
557 :secondary-order secondary-order
558 ))
559 (top-reduction-only nil)
560 (ring *coefficient-ring*))
561 "Returns the K-th elimination ideal of the ideal generated by polynomial list FLIST.
562Thus, a Grobner basis of the ideal generated by FLIST is calculated and
563polynomials depending on variables 0-K are discarded. The monomial order in the
564calculation is an elimination order formed by combining two orders: PRIMARY-ORDER
565used on variables 0-K and SECONDARY-ORDER used on variables starting from variable K+1.
566Thus, if both orders are set to the lexicographic order #'LEX> then the resulting
567order is simply equivalent to #'LEX>. But one could use arbitrary two orders in this
568function, for instance, two copies of #'GREVLEX> (see ORDER package). When doing so,
569the caller must ensure that the same order has been used to sort the terms of
570the polynomials FLIST."
571 (ring-intersection
572 (reduced-grobner flist order start top-reduction-only ring)
573 k))
574
575
576(defun ideal-intersection (F G pred top-reduction-only ring)
577 "Return the Grobner basis of the intersection of the ideals
578generated by the polynomial lists F and G. PRED is an admissible
579monomial order with respect to which the terms of F and G have been
580sorted. This order is going to be used in the Grobner basis
581calculation. If TOP-REDUCTION-ONLY is not NIL, internally the Grobner
582basis algorithm will perform top reduction only. The RING parameter,
583as usual, should be set to a structure defined in the package
584COEFFICIENT-RING, and it will be used to perform all operations on
585coefficients."
586 (mapcar
587 #'poly-contract
588 (ring-intersection
589 (reduced-grobner
590 (append
591 (mapcar #'(lambda (p) (poly-extend p (list 1))) F)
592 (mapcar #'(lambda (p)
593 (append (poly-extend (minus-poly p ring) (list 1))
594 (poly-extend p)))
595 G))
596 (elimination-order-1 pred)
597 0
598 top-reduction-only
599 ring)
600 1)))
601
602
603(defun poly-contract (f &optional (k 1))
604 "Return a polynomial obtained from polynomial F by dropping the
605first K variables, if F does not depend on them. Note that this
606operation makes the polynomial incompatible for certain arithmetical
607operations with the original polynomial F. Calling this function on a polynomial F
608which does depend on variables 0-K will result in error."
609 (when (some #'(lambda (term) (find-if-not #'zerop (car term) :end k)) f)
610 (error "Contracting a polynomial which depends on contracted variables"))
611 (mapcar #'(lambda (term) (cons (nthcdr k (car term)) (cdr term))) f))
612
613
614(defun poly-lcm (f g &optional (pred #'lex>) (ring *coefficient-ring*))
615 "Return LCM (least common multiple) of two polynomials F and G.
616The polynomials must be ordered according to monomial order PRED
617and their coefficients must be compatible with the RING structure
618defined in the COEFFICIENT-RING package."
619 (cond
620 ((endp f) nil)
621 ((endp g) nil)
622 ((and (endp (cdr f)) (endp (cdr g)))
623 (list (cons (monom-lcm (caar f) (caar g))
624 (lcm (cdar f) (cdar g)))))
625 (t
626 (multiple-value-bind (f f-cont)
627 (grobner-primitive-part f ring)
628 (multiple-value-bind (g g-cont)
629 (grobner-primitive-part g ring)
630 (scalar-times-poly
631 (funcall (ring-lcm ring) f-cont g-cont)
632 (grobner-primitive-part (car (ideal-intersection (list f) (list g) pred nil ring))
633 ring)
634 ring))))))
635
636;; GCD of two polynomials, using Grobner bases
637(defun grobner-gcd (f g &optional (pred #'lex>) (ring *coefficient-ring*))
638 "Return GCD (greatest common divisor) of two polynomials F and G.
639The polynomials must be ordered according to monomial order PRED
640and their coefficients must be compatible with the RING structure
641defined in the COEFFICIENT-RING package."
642 (poly-exact-divide (poly* f g pred ring)
643 (poly-lcm f g pred ring)
644 pred ring))
645
646;; Do two Grobner bases yield the same ideal?
647(defun grobner-equal (g1 g2 &optional (pred #'lex>) (ring *coefficient-ring*))
648 "Returns T if two lists of polynomials G1 and G2, assumed to be Grobner bases,
649generate the same ideal, and NIL otherwise."
650 (and (grobner-subsetp g1 g2 pred ring)
651 (grobner-subsetp g2 g1 pred ring)))
652
653(defun grobner-subsetp (g1 g2 &optional (pred #'lex>) (ring *coefficient-ring*))
654 "Returns T if a list of polynomials G1 generates
655an ideal contained in the ideal generated by a polynomial list G2,
656both G1 and G2 assumed to be Grobner bases. Returns NIL otherwise."
657 (every #'(lambda (p) (grobner-member p g2 pred ring)) g1))
658
659(defun grobner-member (p g &optional (pred #'lex>) (ring *coefficient-ring*))
660 "Returns T if a polynomial P belongs to the ideal generated by the
661polynomial list G, which is assumed to be a Grobner basis. Returns NIL otherwise."
662 (endp (normal-form (copy-tree p) g pred nil ring)))
663
664(defun ideal-equal (f1 f2 pred top-reduction-only ring)
665 "Returns T if two ideals generated by polynomial lists F1 and F2 are identical.
666Returns NIL otherwise."
667 (grobner-equal (grobner f1 pred 0 top-reduction-only ring)
668 (grobner f2 pred 0 top-reduction-only ring)
669 pred ring))
670
671(defun ideal-subsetp (f1 f2 &optional (pred #'lex>) (ring *coefficient-ring*))
672 "Returns T if the ideal spanned by the polynomial list F1 is contained
673in the ideal spanned by the polynomial list F2. Returns NIL otherwise."
674 (grobner-subsetp
675 (grobner f1 pred 0 nil ring)
676 (grobner f2 pred 0 nil ring)
677 pred ring))
678
679(defun ideal-member (p plist pred top-reduction-only ring)
680 "Returns T if the polynomial P belongs to the ideal spanned by the polynomial
681list PLIST, and NIL otherwise."
682 (endp (normal-form (copy-tree p) (grobner plist pred 0 top-reduction-only ring)
683 pred nil ring)))
684
685;; Calculate F : p^inf
686(defun ideal-saturation-1 (F p pred start top-reduction-only ring
687 &aux (pred (elimination-order-1 pred)))
688 "Returns the reduced Grobner basis of the saturation of the ideal
689generated by a polynomial list F in the ideal generated by a single
690polynomial P. The saturation ideal is defined as the set of
691polynomials H such for some natural number n (* (EXPT P N) H) is in the ideal
692F. Geometrically, over an algebraically closed field, this is the set
693of polynomials in the ideal generated by F which do not identically
694vanish on the variety of P."
695 (mapcar
696 #'poly-contract
697 (ring-intersection
698 (reduced-grobner
699 (saturation-extension-1 F p ring)
700 pred
701 start top-reduction-only ring)
702 1)))
703
704
705(defun add-variables (plist n)
706 "Add N new variables, adn the first N variables, to every polynomial in polynomial list PLIST.
707The resulting polynomial will not depend on these N variables."
708 (mapcar
709 #'(lambda (g)
710 (mapcar #'(lambda (q) (cons (append (make-list n :initial-element 0)
711 (car q))
712 (cdr q))) g))
713 plist))
714
715;; Calculate <u1*p1,u2*p2,...,uk*pk>
716(defun extend-polynomials (plist &aux (k (length plist)))
717 "Returns polynomial list {U1*P1', U2*P2', ... , UK*PK'}
718where Ui are new variables and PLIST={P1, P2, ... , PK} is a polynomial
719list. PI' is obtained from PI by adding new variables U1, U2, ..., UN
720UK as the first K variables. Thus, the resulting list is consists of polynomials whose
721terms are ordered by the lexicographic order on variables UI, with
722ties resolved by the monomial order which was used to order the terms
723of the polynomials in PLIST. We note that the monomial order does not
724explicitly participate in this calculation, and neither do the
725variable names."
726 (labels ((incf-power (g i)
727 (dolist (x g g)
728 (incf (nth i (car x))))))
729 (setf plist (add-variables plist k))
730 (dotimes (i k plist)
731 (setf (nth i plist) (incf-power (nth i plist) i)))))
732
733;; Calculate <F, u1*p1-1,u2*p2-1,...,uk*pk-1>
734(defun saturation-extension (F plist ring &aux (k (length plist))
735 (d (+ k (length (caaar plist)))))
736 "Returns F' union {U1*P1-1,U2*P2-1,...,UK*PK-1} where Ui are new variables
737and F' is a polynomial list obtained from F by adding variables U1, U2, ..., Uk
738as the first K variables to each polynomial in F. Thus, the resulting list is
739consists of polynomials whose terms are ordered by the lexicographic order on
740variables Ui, with ties resolved by the monomial order which was used to order the
741terms of the polynomials in F. We note that the monomial order does not explicitly
742participate in this calculation, and neither do the variable names."
743 (setf F (add-variables F k)
744 plist (mapcar #'(lambda (x)
745 (nconc x (list (cons (make-list d :initial-element 0)
746 (funcall (ring-- ring)
747 (ring-unit ring))))))
748 (extend-polynomials plist)))
749 (append F plist))
750
751;; Calculate <F, u1*p1+u2*p2+...+uk*pk-1>
752(defun polysaturation-extension (F plist ring &aux (k (length plist))
753 (d (+ k (length (caaar plist)))))
754 "Returns F' union {U1*P1+U2*P2+UK*PK-1} where Ui are new variables
755and F' is a polynomial list obtained from F by adding variables U1, U2, ..., Uk
756as the first K variables to each polynomial in F. Thus, the resulting list is
757consists of polynomials whose terms are ordered by the lexicographic order on
758variables Ui, with ties resolved by the monomial order which was used to order the
759terms of the polynomials in F. We note that the monomial order does not explicitly
760participate in this calculation, and neither do the variable names."
761 (setf F (add-variables F k)
762 plist (apply #'append (extend-polynomials plist))
763 (cdr (last plist)) (list (cons (make-list d :initial-element 0)
764 (funcall (ring-- ring)
765 (ring-unit ring)))))
766 (append F (list plist)))
767
768(defun saturation-extension-1 (F p ring)
769 "Return the list F' union {U*P-1} where U is a new variable,
770where F' is obtained from the polynomial list F by adding U as the first variable.
771The variable U will be added as the first variable, so that it can be easily
772eliminated."
773 (saturation-extension F (list p) ring))
774
775;; Calculate F : p1^inf : p2^inf : ... : ps^inf
776(defun ideal-polysaturation-1 (F plist pred start top-reduction-only ring)
777 "Returns the reduced Grobner basis of the ideal obtained by a
778sequence of successive saturations in the polynomials
779of the polynomial list PLIST of the ideal generated by the
780polynomial list F."
781 (cond
782 ((endp plist) (reduced-grobner F pred start top-reduction-only ring))
783 (t (let ((G (ideal-saturation-1 F (car plist) pred start top-reduction-only ring)))
784 (ideal-polysaturation-1 G (rest plist) pred (length G) top-reduction-only ring)))))
785
786(defun ideal-saturation (F G pred start top-reduction-only ring
787 &aux (k (length G))
788 (pred (elimination-order k
789 :primary-order #'lex>
790 :secondary-order pred)))
791 "Returns the reduced Grobner basis of the saturation of the ideal
792generated by a polynomial list F in the ideal generated a polynomial
793list G The saturation ideal is defined as the set of polynomials H
794such for some natural number n and some P in the ideal generated by G
795the polynomial P**N * H is in the ideal spanned by F. Geometrically,
796over an algebraically closed field, this is the set of polynomials in
797the ideal generated by F which do not identically vanish on the
798variety of G."
799 (mapcar
800 #'(lambda (q) (poly-contract q k))
801 (ring-intersection
802 (reduced-grobner (polysaturation-extension F G ring)
803 pred start
804 top-reduction-only ring)
805 k)))
806
807(defun ideal-polysaturation (F ideal-list pred start top-reduction-only ring)
808 "Returns the reduced Grobner basis of the ideal obtained by a
809successive applications of IDEAL-SATURATIONS to F and
810lists of polynomials in the list IDEAL-LIST."
811 (cond
812 ((endp ideal-list) F)
813 (t (let ((H (ideal-saturation F (car ideal-list) pred start top-reduction-only ring)))
814 (ideal-polysaturation H (rest ideal-list) pred (length H) top-reduction-only ring)))))
815
816(defun buchberger-criterion (G pred ring)
817 "Returns T if G is a Grobner basis, by using the Buchberger
818criterion: for every two polynomials h1 and h2 in G the S-polynomial
819S(h1,h2) reduces to 0 modulo G."
820 (every
821 #'endp
822 (makelist (normal-form (spoly (elt G i) (elt G j) pred ring) G pred nil ring)
823 (i 0 (- (length G) 2))
824 (j (1+ i) (1- (length G))))))
825
826
827(defun grobner-test (G F pred ring)
828 "Test whether G is a Grobner basis and F is contained in G. Return T
829upon success and NIL otherwise."
830 #+debug(debug-cgb "~&GROBNER CHECK: ")
831 (let ((*grobner-debug* nil)
832 (stat1 (buchberger-criterion G pred ring))
833 (stat2
834 (every #'endp
835 (makelist (normal-form (copy-tree (elt F i)) G pred nil ring)
836 (i 0 (1- (length F)))))))
837 (unless stat1 (error "~&Buchberger criterion failed."))
838 (unless stat2
839 (error "~&Original polys not in ideal spanned by Grobner.")))
840 #+debug(debug-cgb "~&GROBNER CHECK END")
841 T)
842
843
844(defun minimization (P pred)
845 "Returns a sublist of the polynomial list P spanning the same
846monomial ideal as P but minimal, i.e. no leading monomial
847of a polynomial in the sublist divides the leading monomial
848of another polynomial."
849 (declare (ignore pred))
850 (do ((Q P)
851 (found t))
852 ((not found) Q)
853 ;;Find p in Q such that lm(p) is in LM(Q\{p})
854 (setf found nil
855 Q (dolist (x Q Q)
856 (let ((Q1 (remove x Q)))
857 (when (member-if #'(lambda (p) (monom-divides-p (lm x) (lm p))) Q1)
858 (setf found t)
859 (return Q1)))))))
860
861
862(defun add-minimized (f Gred pred)
863 "Adds a polynomial f to GRED, reduced Grobner basis, preserving the
864property described in the documentation for MINIMIZATION."
865 (if (member-if #'(lambda (p) (monom-divides-p (lm p) (lm f))) Gred)
866 Gred
867 (merge 'list (list f)
868 (delete-if #'(lambda (p) (monom-divides-p (lm f) (lm p))) Gred)
869 pred :key #'lm)))
870
871(defun colon-ideal (F G pred top-reduction-only ring)
872 "Returns the reduced Grobner basis of the colon ideal Id(F):Id(G), where
873F and G are two lists of polynomials. The colon ideal I:J is defined as the
874set of polynomials H such that there is a polynomial W in J for which
875W*H belongs to I."
876 (cond
877 ((endp G)
878 (if (every #'endp F) nil
879 (list (list
880 (cons
881 (make-list (length (caar (find-if-not #'endp F)))
882 :initial-element 0)
883 1)))))
884 ((endp (cdr G))
885 (colon-ideal-1 F (car G) pred top-reduction-only ring))
886 (t
887 (ideal-intersection (colon-ideal-1 F (car G) pred top-reduction-only ring)
888 (colon-ideal F (rest G) pred top-reduction-only ring)
889 pred
890 top-reduction-only
891 ring))))
892
893(defun colon-ideal-1 (F g pred top-reduction-only ring)
894 "Returns the reduced Grobner basis of the colon ideal Id(F):Id({G}), where
895F is a list of polynomials and G is a polynomial."
896 (mapcar #'(lambda (x) (poly-exact-divide x g pred ring))
897 (ideal-intersection F (list g) pred top-reduction-only ring)))
898
899
900(defun pseudo-divide (f fl pred ring)
901 "Pseudo-divide a polynomial F by the list of polynomials FL. Return
902multiple values. The first value is a list of quotients A.
903The second value is the remainder R. The third value is an integer
904count of the number of reductions performed. Finally, the fourth
905argument is a scalar coefficient C, such that C*F can be divided by FL
906within the ring of coefficients, which is not necessarily a field.
907The resulting objects satisfy the equation:
908 C*F= sum A[i]*FL[i] + R
909"
910 (declare (optimize (speed 3) (safety 0)))
911 (do (r
912 (c (ring-unit ring))
913 (a (make-list (length fl)))
914 (division-count 0)
915 (p f))
916 ((endp p)
917 #+debug(debug-cgb "~&~3T~d reduction~:p" division-count)
918 #+debug(when (endp r) (debug-cgb " ---> 0"))
919 (values a (nreverse r) division-count c))
920 (declare (fixnum division-count) (integer c))
921 (do ((fl fl (rest fl)) ;scan list of divisors
922 (b a (rest b)))
923 ((cond
924 ((endp fl) ;no division occurred
925 (setf r (cons (lt p) r) ;move lt(p) to remainder
926 p (rest p)) ;remove lt(p) from p
927 t)
928 ((monom-divides-p (lm (car fl)) (lm p)) ;division occurred
929 (incf division-count)
930 (let* ((gcd (funcall (ring-gcd ring) (lc (car fl)) (lc p)))
931 (c1 (funcall (ring-/ ring) (lc (car fl)) gcd))
932 (c2 (funcall (ring-/ ring) (lc p) gcd))
933 (quot (cons (monom/ (lm p) (lm (car fl))) c2)))
934 ;; Multiply the equation c*f=sum ai*fi+r+p by c1.
935 (mapl #'(lambda (x)
936 (setf (car x) (scalar-times-poly c1 (car x) ring)))
937 a)
938 (setf p (scalar-times-poly c1 (rest p) ring) ;drop first term
939 r (scalar-times-poly c1 r ring)
940 c (funcall (ring-* ring) c c1)
941 p (poly-op p quot (rest (car fl)) pred ring)
942 (car b) (nconc (car b) (list quot))))
943 t))))))
944
945;;----------------------------------------------------------------
946;; An implementation of the algorithm of Gebauer and Moeller,
947;; as described in the book of Becker-Weispfenning, p. 232
948;;----------------------------------------------------------------
949(defun gebauer-moeller (F pred start top-reduction-only ring
950 &aux B G F1)
951 "Compute Grobner basis by using the algorithm of Gebauer and Moeller.
952This algorithm is described as BUCHBERGERNEW2 in the book by
953Becker-Weispfenning entitled ``Grobner Bases''"
954 ;;cut startup costs if (length F)<=1
955 (cond
956 ((endp F) (return-from gebauer-moeller nil))
957 ((endp (cdr F))
958 (return-from gebauer-moeller (list (grobner-primitive-part (car F) ring)))))
959 #+debug (debug-cgb "~&GROBNER BASIS - GEBAUER MOELLER ALGORITHM")
960 #+debug (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
961 #+grobner-check (when (plusp start)
962 (grobner-test (subseq F 0 start) (subseq F 0 start)
963 pred ring))
964 (setf B nil
965 G (subseq F 0 start)
966 F1 (subseq F start))
967 (do () ((endp F1))
968 (multiple-value-setq (G B)
969 (update G B (grobner-primitive-part (pop F1) ring) pred ring)))
970 (do () ((endp B))
971 (let* ((pair (pop B))
972 (g1 (first pair))
973 (g2 (second pair))
974 (h (normal-form (spoly g1 g2 pred ring)
975 G pred top-reduction-only ring)))
976 (unless (poly-zerop h)
977 (setf h (grobner-primitive-part h ring))
978 (multiple-value-setq (G B)
979 (update G B h pred ring))
980 #+debug (debug-cgb "~&Polynomials: ~d; Pairs left: ~d~%"
981 (length G) (length B))
982 )))
983 #+grobner-check(grobner-test G F pred ring)
984 #+debug(debug-cgb "~&GROBNER END")
985 G)
986
987(defun update (G B h pred ring &aux C D E B-new G-new pair)
988 "An implementation of the auxillary UPDATE algorithm used by the
989Gebauer-Moeller algorithm. G is a list of polynomials, B is a list of
990critical pairs and H is a new polynomial which possibly will be added
991to G. The naming conventions used are very close to the one used in
992the book of Becker-Weispfenning."
993 (setf C G D nil)
994 (do (g1) ((endp C))
995 (setf g1 (pop C))
996 (when (or (monom-rel-prime (lm h) (lm g1))
997 (and
998 (not (some
999 #'(lambda (g2) (monom-divides-p (monom-lcm (lm h) (lm g2))
1000 (monom-lcm (lm h) (lm g1))))
1001 C))
1002 (not (some
1003 #'(lambda (g2) (monom-divides-p (monom-lcm (lm h) (lm g2))
1004 (monom-lcm (lm h) (lm g1))))
1005 D))))
1006 (push g1 D)))
1007 (setf E nil)
1008 (do (g1) ((endp D))
1009 (setf g1 (pop D))
1010 (unless (monom-rel-prime (lm h) (lm g1))
1011 (push g1 E)))
1012 (setf B-new nil)
1013 (do (g1 g2) ((endp B))
1014 (setf pair (pop B)
1015 g1 (first pair)
1016 g2 (second pair))
1017 (when (or (not (monom-divides-p (lm h) (monom-lcm (lm g1) (lm g2))))
1018 (equal (monom-lcm (lm g1) (lm h))
1019 (monom-lcm (lm g1) (lm g2)))
1020 (equal (monom-lcm (lm h) (lm g2))
1021 (monom-lcm (lm g1) (lm g2))))
1022 (setf B-new (funcall *gebauer-moeller-merge-pairs* B-new (list (list g1 g2)) pred ring))))
1023 (dolist (g3 E)
1024 (setf B-new (funcall *gebauer-moeller-merge-pairs* B-new (list (list h g3)) pred ring)))
1025 (setf G-new nil)
1026 (do (g1) ((endp G))
1027 (setf g1 (pop G))
1028 (unless (monom-divides-p (lm h) (lm g1))
1029 (push g1 G-new)))
1030 (push h G-new)
1031 (values G-new B-new))
1032
1033(defun gebauer-moeller-merge-pairs-use-mock-spoly (B C pred ring)
1034 "The merging strategy used by the Gebauer-Moeller algorithm, based
1035on MOCK-SPOLY; see the documentation of
1036BUCHBERGER-MERGE-PAIRS-USE-MOCK-SPOLY."
1037 (declare (ignore ring))
1038 ;; Delete pairs consisting of two single monomials
1039 (setf C (delete-if
1040 #'(lambda (p) (and (endp (cdr (first p)))
1041 (endp (cdr (second p)))))
1042 C))
1043 (labels ((pair-key (p) (mock-spoly (first p) (second p) pred))
1044 (pair-order (x y) (funcall pred y x)))
1045 (merge 'list B C #'pair-order :key #'pair-key)))
1046
1047(defun gebauer-moeller-merge-pairs-smallest-lcm (B C pred ring)
1048 "The merging strategy based on the smallest-lcm (normal strategy); see
1049the documentation of BUCHBERGER-MERGE-PAIRS-SMALLEST-LCM."
1050 (declare (ignore ring))
1051 ;; Delete pairs consisting of two single monomials
1052 (labels ((pair-key (p) (monom-lcm (lm (first p))
1053 (lm (second p))))
1054 (pair-order (x y) (funcall pred y x)))
1055 (merge 'list B C #'pair-order :key #'pair-key)))
1056
1057
1058(defun gebauer-moeller-merge-pairs-use-smallest-degree (B C pred ring)
1059 "The merging strategy based on the smallest-lcm (normal strategy); see
1060the documentation of BUCHBERGER-MERGE-PAIRS-USE-SMALLEST-DEGREE."
1061 (declare (ignore ring))
1062 (declare (ignore pred))
1063 (labels ((pair-key (p) (total-degree
1064 (monom-lcm (lm (first p))
1065 (lm (second p)))))
1066 (pair-order (x y) (funcall #'< x y)))
1067 (merge 'list B C #'pair-order :key #'pair-key)))
1068
1069
1070(defun gebauer-moeller-merge-pairs-use-smallest-length (B C pred ring)
1071 (declare (ignore ring))
1072 "The merging strategy based on the smallest-lcm (normal strategy); see
1073the documentation of BUCHBERGER-MERGE-PAIRS-USE-SMALLEST-LENGTH."
1074 (declare (ignore pred))
1075 (labels ((pair-key (p) (+
1076 (length (first p))
1077 (length (second p))))
1078 (pair-order (x y) (funcall #'< x y)))
1079 (if B
1080 (merge 'list B C #'pair-order :key #'pair-key)
1081 (sort C #'pair-order :key #'pair-key))))
1082
1083
1084(defun gebauer-moeller-merge-pairs-use-smallest-coefficient-length (B C pred ring)
1085 "The merging strategy based on the smallest-lcm (normal strategy); see
1086the documentation of BUCHBERGER-MERGE-PAIRS-USE-SMALLEST-COEFFICIENT-LENGTH."
1087 (declare (ignore pred))
1088 (labels ((coefficient-length (poly)
1089 (apply #'+ (mapcar (ring-length ring) (mapcar #'cdr poly))))
1090 (pair-key (p) (+
1091 (coefficient-length (first p))
1092 (coefficient-length (second p))))
1093 (pair-order (x y) (funcall #'< x y)))
1094 (merge 'list B C #'pair-order :key #'pair-key)))
1095
1096(defun gebauer-moeller-set-pair-heuristic
1097 (method
1098 &aux (strategy-fn
1099 (ecase method
1100 (:minimal-mock-spoly #'gebauer-moeller-merge-pairs-use-mock-spoly)
1101 (:minimal-lcm #'gebauer-moeller-merge-pairs-smallest-lcm)
1102 (:minimal-total-degree #'gebauer-moeller-merge-pairs-use-smallest-degree)
1103 (:minimal-length #'gebauer-moeller-merge-pairs-use-smallest-length)
1104 (:minimal-coefficient-length #'gebauer-moeller-merge-pairs-use-smallest-coefficient-length))))
1105 (setf *gebauer-moeller-merge-pairs* strategy-fn))
1106
1107;;------------------------------------------------------------------------------------------------
1108;;
1109;; An implementation of the sugar strategy
1110;;
1111;;------------------------------------------------------------------------------------------------
1112
1113;; Calculate sugar of the S-polynomial of f and g
1114(defun spoly-sugar (f-with-sugar g-with-sugar ring)
1115 "Calculate the ``sugar'' of the S-polynomial of two polynomials with
1116sugar. A polynomial with sugar is simply a pair (P . SUGAR) where
1117SUGAR is an integer constant defined according to the following
1118algorighm: the sugar of sum or difference of two polynomials with
1119sugar is the MAX of the sugars of those two polynomials. The sugar of
1120a product of a term and a polynomial is the sum of the degree of the
1121term and the sugar of the polynomial. The idea is to accumulate sugar
1122as we perform the arithmetic operations, and that polynomials with
1123small (little) sugar should be given priority in the calculations.
1124Thus, the ``sugar strategy'' of the critical pair selection is to
1125select a pair with the smallest value of sugar of the resulting
1126S-polynomial."
1127 (let* ((f (poly-with-sugar-poly f-with-sugar))
1128 (g (poly-with-sugar-poly g-with-sugar))
1129 (lcm (monom-lcm (lm f) (lm g)))
1130 (m1 (monom/ lcm (lm f)))
1131 (m2 (monom/ lcm (lm g))))
1132 (let* ((c (funcall (ring-lcm ring) (lc f) (lc g)))
1133 (cf (funcall (ring-/ ring) c (lc f)))
1134 (cg (funcall (ring-/ ring) c (lc g))))
1135 (max
1136 (+ (term-sugar (cons m1 cf) ring) (poly-with-sugar-sugar f-with-sugar))
1137 (+ (term-sugar (cons m2 cg) ring) (poly-with-sugar-sugar g-with-sugar))))))
1138
1139;; Calculate the S-polynomial of f and g with sugar
1140(defun spoly-with-sugar (f-with-sugar g-with-sugar pred ring)
1141 "The S-polynomials of two polynomials with SUGAR strategy."
1142 (let* ((f (poly-with-sugar-poly f-with-sugar))
1143 (g (poly-with-sugar-poly g-with-sugar))
1144 (lcm (monom-lcm (lm f) (lm g)))
1145 (m1 (monom/ lcm (lm f)))
1146 (m2 (monom/ lcm (lm g))))
1147 (let* ((c (funcall (ring-lcm ring) (lc f) (lc g)))
1148 (cf (funcall (ring-/ ring) c (lc f)))
1149 (cg (funcall (ring-/ ring) c (lc g))))
1150 (poly-with-sugar-
1151 (term-times-poly-with-sugar (cons m1 cf) (poly-with-sugar-tail f-with-sugar) ring)
1152 (term-times-poly-with-sugar (cons m2 cg) (poly-with-sugar-tail g-with-sugar) ring)
1153 pred
1154 ring))))
1155
1156
1157(defun normal-form-with-sugar (f fl pred top-reduction-only ring)
1158 "Normal form of the polynomial with sugar F with respect to
1159a list of polynomials with sugar FL. Assumes that FL is not empty.
1160Parameters PRED, TOP-REDUCTION-ONLY and RING have the same meaning as in NORMAL-FORM.
1161The parameter SUGAR-LIMIT should be set to a positive integer. If the sugar limit of
1162the partial remainder exceeds SUGAR-LIMIT then the calculation is stopped and the partial
1163remainder is returned, although it is not fully reduced with respect to FL."
1164 (declare (optimize (speed 3) (safety 0)))
1165 ;; Loop invariant: c*f=sum ai*fi+r+p
1166 (do ((r (cons nil 0))
1167 (c (ring-unit ring))
1168 (division-count 0)
1169 (p f))
1170 ((or (poly-with-sugar-zerop p)
1171 (and top-reduction-only (not (poly-with-sugar-zerop r))))
1172 #+debug
1173 (progn
1174 (debug-cgb "~&~3T~d reduction~:p" division-count)
1175 (cond
1176 ((poly-with-sugar-zerop r)
1177 (debug-cgb " ---> 0"))))
1178 (values (poly-with-sugar-append (poly-with-sugar-nreverse r) p)
1179 division-count c))
1180 (declare (fixnum division-count) (integer c))
1181 (let ((g (find (poly-with-sugar-lm p) fl
1182 :test #'monom-divisible-by-p
1183 :key #'poly-with-sugar-lm)))
1184 (cond
1185 (g ;division possible
1186 (incf division-count)
1187 (let* ((gcd (funcall (ring-gcd ring) (poly-with-sugar-lc g) (poly-with-sugar-lc p)))
1188 (c1 (funcall (ring-/ ring) (poly-with-sugar-lc g) gcd))
1189 (c2 (funcall (ring-/ ring) (poly-with-sugar-lc p) gcd))
1190 (m (monom/ (poly-with-sugar-lm p) (poly-with-sugar-lm g))))
1191 ;; Multiply the equation c*f=sum ai*fi+r+p by c1.
1192 (setf r (scalar-times-poly-with-sugar c1 r ring)
1193 c (funcall (ring-* ring) c c1)
1194 p (scalar-times-poly-with-sugar c1 p ring)
1195 p (poly-with-sugar-op p (cons m c2) g pred ring))))
1196 (t ;no division possible
1197 ;;move lt(p) to remainder
1198 (setf r (cons (cons (poly-with-sugar-lt p) (poly-with-sugar-poly r))
1199 (poly-with-sugar-sugar r))
1200 p (poly-with-sugar-tail p)))))))
1201
1202;; Parameter START is used when Grobner basis is calculated incrementally
1203;; and it signals that the elements of F from 0 to START-1 form a Grobner
1204;; basis already, so their pairs are not formed.
1205(defun buchberger-with-sugar (F-no-sugar pred start top-reduction-only ring
1206 &aux (s (1- (length F-no-sugar))) B M F)
1207 "Returns a Grobner basis of an ideal generated by a list of ordinary
1208polynomials F-NO-SUGAR. Adds initial sugar to the polynomials and
1209performs the Buchberger algorithm with ``sugar strategy''. It returns
1210an ordinary list of polynomials with no sugar. One of the most
1211effective algorithms for Grobner basis calculation."
1212 (declare (fixnum s))
1213 (unless (plusp s) (return-from buchberger-with-sugar F-no-sugar)) ;cut startup costs
1214 #+debug (debug-cgb "~&GROBNER BASIS - BUCHBERGER WITH SUGER STRATEGY ALGORITHM")
1215 #+debug (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
1216 #+grobner-check (when (plusp start)
1217 (grobner-test (subseq F-no-sugar 0 start)
1218 (subseq F-no-sugar 0 start) pred ring))
1219 (setf F (mapcar #'(lambda (x) (poly-add-sugar x ring)) F-no-sugar)
1220 B (nconc (makelist (list i j) (i 0 (1- start)) (j start s))
1221 (makelist (list i j) (i start (1- s)) (j (1+ i) s)))
1222 M (make-hash-table :test #'equal))
1223 ;;Initialize treated pairs
1224 (dotimes (i (1- start))
1225 (do ((j (1+ i) (1+ j))) ((>= j start))
1226 (setf (gethash (list i j) M) t)))
1227 (setf B (buchberger-with-sugar-sort-pairs B F M pred ring))
1228 (do ((G F))
1229 ((endp B)
1230 (setf G (mapcar #'poly-with-sugar-poly G))
1231 ;;#+grobner-check(grobner-test G F-no-sugar pred ring)
1232 #+debug(debug-cgb "~&GROBNER END")
1233 G)
1234 (let ((pair (pop B)))
1235 (cond
1236 ((Criterion-1-with-sugar pair G))
1237 ((Criterion-2-with-sugar pair G M))
1238 (t
1239 (let ((SP (normal-form-with-sugar
1240 (cons (spoly (poly-with-sugar-poly (elt G (first pair)))
1241 (poly-with-sugar-poly (elt G (second pair))) pred ring)
1242 (third pair))
1243 G pred top-reduction-only ring)))
1244 (cond
1245 ((poly-with-sugar-zerop SP))
1246 (t
1247 (setf s (1+ s)
1248 (poly-with-sugar-poly SP) (grobner-primitive-part
1249 (poly-with-sugar-poly SP) ring)
1250 (cdr (last G)) (list SP)
1251 B (buchberger-with-sugar-merge-pairs B (makelist (list i s)
1252 (i 0 (1- s)))
1253 G M pred ring))
1254 #+debug (debug-cgb "~&[~d] Polynomials: ~d; Pairs left: ~d; Treated pairs: ~d"
1255 (third pair)
1256 (length G) (length B)
1257 (hash-table-count M)))))))
1258 (setf (cddr pair) nil
1259 (gethash pair M) t))))
1260
1261
1262(defun buchberger-with-sugar-merge-pairs (B C G M pred ring)
1263 "Merges lists of critical pairs. It orders pairs according to
1264increasing sugar, with ties broken by smaller MOCK-SPOLY value of the
1265two polynomials. In this function B must already be sorted."
1266 ;;Remove pairs consisting of two monomials
1267 ;;These pairs produce zero S-polynomial
1268 (setf C (delete-if
1269 #'(lambda (p)
1270 (when (and (endp (cdr (poly-with-sugar-poly (elt G (first p)))))
1271 (endp (cdr (poly-with-sugar-poly (elt G (second p))))))
1272 ;;Record the pair as treated
1273 (setf (gethash p M) t)
1274 t))
1275 C))
1276 (labels ((pair-sugar (p)
1277 (spoly-sugar (elt G (first p)) (elt G (second p)) ring))
1278 (pair-mock-spoly (p)
1279 (mock-spoly (poly-with-sugar-poly (elt G (first p)))
1280 (poly-with-sugar-poly (elt G (second p))) pred))
1281 (pair-order (p q)
1282 (let ((sugar-p (third p))
1283 (sugar-q (third q)))
1284 (cond
1285 ((< sugar-p sugar-q) t)
1286 ((> sugar-p sugar-q) nil)
1287 (t
1288 (funcall pred (fourth q) (fourth p)))))))
1289 ;;Add sugar and mock S-polynomial as the third and fourth element
1290 ;;of new pair in C
1291 (dolist (p C)
1292 (setf (cdr (last p))
1293 (list (pair-sugar p) (pair-mock-spoly p))))
1294 (merge 'list B (sort C #'pair-order) #'pair-order)))
1295
1296(defun buchberger-with-sugar-sort-pairs (C G M pred ring)
1297 "Sorts critical pairs C according to sugar strategy."
1298 (buchberger-with-sugar-merge-pairs nil C G M pred ring))
1299
1300(defun Criterion-1-with-sugar (pair G &aux (i (first pair)) (j (second pair)))
1301 "An implementation of Buchberger's first criterion for polynomials
1302with sugar. See the documentation of BUCHBERGER-CRITERION-1."
1303 (monom-rel-prime (poly-with-sugar-lm (elt G i))
1304 (poly-with-sugar-lm (elt G j))))
1305
1306(defun Criterion-2-with-sugar (pair G M &aux (i (first pair)) (j (second pair)))
1307 "An implementation of Buchberger's first criterion for polynomials
1308with sugar. See the documentation of BUCHBERGER-CRITERION-2."
1309 (labels ((make-pair (u v) (if (< u v) (list u v) (list v u))))
1310 (dotimes (k (length G) nil)
1311 (when (and (/= k i)
1312 (/= k j)
1313 (monom-divides-p
1314 (poly-with-sugar-lm (elt G k))
1315 (monom-lcm (poly-with-sugar-lm (elt G i))
1316 (poly-with-sugar-lm (elt G j))))
1317 (gethash (make-pair i k) M)
1318 (gethash (make-pair k j) M))
1319 #+debug(when *grobner-debug* (format t ":B2"))
1320 (return-from Criterion-2-with-sugar t)))))
1321
1322
1323;;----------------------------------------------------------------
1324;; An implementation of the algorithm of Gebauer and Moeller,
1325;; as described in the book of Becker-Weispfenning, p. 232
1326;; with sugar strategy
1327;;----------------------------------------------------------------
1328(defun gebauer-moeller-with-sugar (F pred start top-reduction-only ring
1329 &aux B G F1)
1330 "Compute Grobner basis by using the algorithm of Gebauer and Moeller.
1331This algorithm is described as BUCHBERGERNEW2 in the book by
1332Becker-Weispfenning entitled ``Grobner Bases''"
1333 ;;cut startup costs if (length F)<=1
1334 (cond
1335 ((endp F) (return-from gebauer-moeller-with-sugar nil))
1336 ((endp (cdr F))
1337 (return-from gebauer-moeller-with-sugar (list (grobner-primitive-part (car F) ring)))))
1338 #+debug (debug-cgb "~&GROBNER BASIS - GEBAUER MOELLER ALGORITHM WITH SUGAR STRATEGY")
1339 #+debug (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
1340 #+grobner-check (when (plusp start)
1341 (grobner-test (subseq F 0 start) (subseq F 0 start)
1342 pred ring))
1343 (setf B nil
1344 G (subseq F 0 start)
1345 F1 (subseq F start))
1346 ;;Initialize sugar
1347 (setf G (mapcar #'(lambda (x) (poly-add-sugar x ring)) G)
1348 F1 (mapcar #'(lambda (x) (poly-add-sugar x ring)) F1))
1349 (do () ((endp F1))
1350 (multiple-value-setq (G B)
1351 (update-with-sugar G B (grobner-primitive-part-with-sugar (pop F1) ring) pred ring)))
1352 (do ()
1353 ((endp B))
1354 (let* ((pair (pop B))
1355 (g1 (first pair))
1356 (g2 (second pair))
1357 (h (normal-form-with-sugar (spoly-with-sugar g1 g2 pred ring)
1358 G pred top-reduction-only ring)))
1359 (cond
1360 ((poly-with-sugar-zerop h))
1361 (t
1362 (setf h (grobner-primitive-part-with-sugar h ring))
1363 (multiple-value-setq (G B)
1364 (update-with-sugar G B h pred ring))
1365 #+debug (debug-cgb "~&[[~d]] Polynomials: ~d; Pairs left: ~d~%"
1366 (poly-with-sugar-sugar h)
1367 (length G) (length B))
1368 ))))
1369 (setf G (mapcar #'poly-with-sugar-poly G))
1370 ;;#+grobner-check(grobner-test G F pred ring)
1371 #+debug(debug-cgb "~&GROBNER END")
1372 G)
1373
1374(defun update-with-sugar (G B h pred ring &aux C D E B-new G-new pair)
1375 "An implementation of the auxillary UPDATE algorithm used by the
1376Gebauer-Moeller algorithm. G is a list of polynomials, B is a list of
1377critical pairs and H is a new polynomial which possibly will be added
1378to G. The naming conventions used are very close to the one used in
1379the book of Becker-Weispfenning. Operates on polynomials with sugar."
1380 (setf C G D nil)
1381 (do (g1) ((endp C))
1382 (setf g1 (pop C))
1383 (when (or (monom-rel-prime (poly-with-sugar-lm h) (poly-with-sugar-lm g1))
1384 (and
1385 (not (some
1386 #'(lambda (g2) (monom-divides-p (monom-lcm (poly-with-sugar-lm h)
1387 (poly-with-sugar-lm g2))
1388 (monom-lcm (poly-with-sugar-lm h)
1389 (poly-with-sugar-lm g1))))
1390 C))
1391 (not (some
1392 #'(lambda (g2) (monom-divides-p (monom-lcm (poly-with-sugar-lm h)
1393 (poly-with-sugar-lm g2))
1394 (monom-lcm (poly-with-sugar-lm h)
1395 (poly-with-sugar-lm g1))))
1396 D))))
1397 (push g1 D)))
1398 (setf E nil)
1399 (do (g1) ((endp D))
1400 (setf g1 (pop D))
1401 (unless (monom-rel-prime (poly-with-sugar-lm h) (poly-with-sugar-lm g1))
1402 (push g1 E)))
1403 (setf B-new nil)
1404 (do (g1 g2) ((endp B))
1405 (setf pair (pop B)
1406 g1 (first pair)
1407 g2 (second pair))
1408 (when (or (not (monom-divides-p (poly-with-sugar-lm h) (monom-lcm (poly-with-sugar-lm g1)
1409 (poly-with-sugar-lm g2))))
1410 (equal (monom-lcm (poly-with-sugar-lm g1) (poly-with-sugar-lm h))
1411 (monom-lcm (poly-with-sugar-lm g1) (poly-with-sugar-lm g2)))
1412 (equal (monom-lcm (poly-with-sugar-lm h) (poly-with-sugar-lm g2))
1413 (monom-lcm (poly-with-sugar-lm g1) (poly-with-sugar-lm g2))))
1414 (setf B-new (gebauer-moeller-with-sugar-merge-pairs B-new (list (list g1 g2)) pred ring))))
1415 (dolist (g3 E)
1416 (setf B-new (gebauer-moeller-with-sugar-merge-pairs B-new (list (list h g3)) pred ring)))
1417 (setf G-new nil)
1418 (do (g1) ((endp G))
1419 (setf g1 (pop G))
1420 (unless (monom-divides-p (poly-with-sugar-lm h) (poly-with-sugar-lm g1))
1421 (push g1 G-new)))
1422 (push h G-new)
1423 (values G-new B-new))
1424
1425(defun gebauer-moeller-with-sugar-merge-pairs (B C pred ring)
1426 "Merges lists of critical pairs. It orders pairs according to
1427increasing sugar, with ties broken by smaller lcm of head monomials In
1428this function B must already be sorted. Operates on polynomials with sugar."
1429 (setf C (delete-if
1430 #'(lambda (p) (and (endp (cdr (first p)))
1431 (endp (cdr (second p)))))
1432 C))
1433 (labels ((pair-sugar (p)
1434 (spoly-sugar (first p) (second p) ring))
1435 (pair-mock-spoly (p)
1436 (mock-spoly (poly-with-sugar-poly (first p))
1437 (poly-with-sugar-poly (second p)) pred))
1438 (pair-order (p q)
1439 (let ((sugar-p (pair-sugar p))
1440 (sugar-q (pair-sugar q)))
1441 (cond
1442 ((< sugar-p sugar-q) t)
1443 ((> sugar-p sugar-q) nil)
1444 (t
1445 (funcall pred (pair-mock-spoly q) (pair-mock-spoly p)))))))
1446 (merge 'list B (sort C #'pair-order) #'pair-order)))
1447
1448(defun grobner-primitive-part-with-sugar (h ring)
1449 (cons (grobner-primitive-part (car h) ring) (cdr h)))
1450
1451;;----------------------------------------------------------------
1452;;
1453;; An implementation of the algorithms using product caching
1454;;
1455;;----------------------------------------------------------------
1456(defun cached-normal-form (f fl pred top-reduction-only ring cache)
1457 "This version of NORMAL-FORM uses a cache which stores products of monomials
1458and polynomials found in FL. The cache is a hash table storing pairs (G . G-HASH-TABLE)
1459where G is a polynomial in FL serving as a key. The hash table G-HASH-TABLE is a list
1460of pairs (MONOMIAL . PRODUCT-POLY) where PRODUCT-POLY is (POLY* MONOMIAL G)."
1461
1462 (declare (optimize (speed 3) (safety 0)))
1463 ;; Loop invariant: c*f=sum ai*fi+r+p
1464 (do (r (c (ring-unit ring))
1465 (division-count 0)
1466 (p f))
1467 ((or (endp p)
1468 (endp fl)
1469 (and top-reduction-only r))
1470 #+debug(progn
1471 (debug-cgb "~&~3T~d reduction~:p" division-count)
1472 (when (endp r)
1473 (debug-cgb " ---> 0")))
1474 (values (append (nreverse r) p)
1475 division-count c))
1476 (declare (fixnum division-count) (integer c))
1477 (let ((i (position (lm p) fl :test #'monom-divisible-by-p :key #'lm)))
1478 (cond
1479 (i ;division possible
1480 (incf division-count)
1481 (let* ((g (nth i fl))
1482 (hash-tab (nth i cache))
1483 (gcd (funcall (ring-gcd ring) (lc g) (lc p)))
1484 (c1 (funcall (ring-/ ring) (lc g) gcd))
1485 (c2 (funcall (ring-/ ring) (lc p) gcd))
1486 (m (monom/ (lm p) (lm g))))
1487 ;; Multiply the equation c*f=sum ai*fi+r+p by c1.
1488 (setf r (scalar-times-poly c1 r ring)
1489 c (funcall (ring-* ring) c c1)
1490 p (cached-grobner-op c2 c1 m p g pred ring hash-tab))))
1491 (t ;no division possible
1492 (setf r (cons (lt p) r) ;move lt(p) to remainder
1493 p (rest p)))))))
1494
1495(defun cached-grobner-op (c1 c2 m A B pred ring cache)
1496 "Returns the same result as (GROBNER-OP C1 C2 M A B PRED RING) but
1497it used variable CACHE which is described in CACHED-NORMAL-FORM for
1498efficient calculation of products of monomials with polynomials."
1499 (poly- (scalar-times-poly c2 A)
1500 (scalar-times-poly c1 (cached-monom-times-poly m B cache) ring)
1501 pred ring))
1502
1503(defun cached-buchberger (F pred start top-reduction-only ring
1504 &aux (s (1- (length F))) B M CACHE)
1505 "It returns the same result as BUCHBERGER but it uses caching
1506of products of monomials with polynomials."
1507 (declare (fixnum s))
1508 (unless (plusp s) (return-from cached-buchberger F)) ;cut startup costs
1509 #+debug (debug-cgb "~&GROBNER BASIS - CACHED BUCHBERGER ALGORITHM")
1510 #+debug (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
1511 #+grobner-check (when (plusp start)
1512 (grobner-test (subseq F 0 start) (subseq F 0 start) pred ring))
1513 (setf B (nconc (makelist (list i j) (i 0 (1- start)) (j start s))
1514 (makelist (list i j) (i start (1- s)) (j (1+ i) s)))
1515 M (make-hash-table :test #'equal)
1516 B (buchberger-sort-pairs B F pred ring))
1517 ;;Initialize cache
1518 (dotimes (k (1+ s)) (push (make-hash-table :test #'equal) CACHE))
1519 ;;Initialize treated pairs
1520 (dotimes (i (1- start))
1521 (do ((j (1+ i) (1+ j))) ((>= j start))
1522 (setf (gethash (list i j) M) t)))
1523 (do ((G F))
1524 ((endp B)
1525 #+grobner-check(grobner-test G F pred ring)
1526 #+debug(debug-cgb "~&GROBNER END")
1527 G)
1528 (let ((pair (pop B)))
1529 (unless (or (Criterion-1 pair G)
1530 (Criterion-2 pair G M))
1531 (let ((SP (cached-normal-form (cached-spoly (elt G (first pair))
1532 (elt G (second pair))
1533 pred
1534 ring
1535 (elt CACHE (first pair))
1536 (elt CACHE (second pair)))
1537 G pred top-reduction-only ring CACHE)))
1538 (unless (poly-zerop SP) ;S-polynomial ---> 0;
1539 (setf s (1+ s)
1540 SP (grobner-primitive-part SP ring)
1541 (cdr (last G)) (list SP)
1542 (cdr (last Cache)) (list (make-hash-table :test #'equal))
1543 B (funcall *buchberger-merge-pairs* B (makelist (list i s)
1544 (i 0 (1- s)))
1545 G pred ring))
1546 #+debug (debug-cgb "~&Polynomials: ~d; Pairs left: ~d; Treated pairs: ~d"
1547 (length G) (length B)
1548 (hash-table-count M)))))
1549 (setf (gethash pair M) t))))
1550
1551(defun cached-spoly (f g pred ring cache-f cache-g)
1552 "Uses CACHE to fetch products of monomials and polynomials."
1553 (declare (optimize (speed 3) (safety 0)))
1554 (let* ((lcm (monom-lcm (lm f) (lm g)))
1555 (m1 (monom/ lcm (lm f)))
1556 (m2 (monom/ lcm (lm g))))
1557 (let* ((c (funcall (ring-lcm ring) (lc f) (lc g)))
1558 (cf (funcall (ring-/ ring) c (lc f)))
1559 (cg (funcall (ring-/ ring) c (lc g))))
1560 (poly-
1561 (scalar-times-poly cf (cached-monom-times-poly m1 f cache-f) ring)
1562 (scalar-times-poly cg (cached-monom-times-poly m2 g cache-g) ring)
1563 pred
1564 ring))))
1565
1566
1567(defun cached-monom-times-poly (m f cache)
1568 (let ((prod (gethash m cache)))
1569 (cond
1570 (prod #+debug(debug-cgb "c") prod)
1571 (t
1572 #+debug(debug-cgb ".")
1573 (setf (gethash m cache) (monom-times-poly m f))))))
1574
1575;;------------------------------------------------------------------------------------------------
1576;;
1577;; An implementation of the sugar strategy with product caching
1578;;
1579;;------------------------------------------------------------------------------------------------
1580(defun cached-normal-form-with-sugar (f fl pred top-reduction-only ring cache)
1581 "Normal form of the polynomial with sugar F with respect to
1582a list of polynomials with sugar FL. Assumes that FL is not empty.
1583Parameters PRED, TOP-REDUCTION-ONLY and RING have the same meaning as in NORMAL-FORM.
1584The parameter SUGAR-LIMIT should be set to a positive integer. If the sugar limit of
1585the partial remainder exceeds SUGAR-LIMIT then the calculation is stopped and the partial
1586remainder is returned, although it is not fully reduced with respect to FL."
1587 (declare (optimize (speed 3) (safety 0)))
1588 ;; Loop invariant: c*f=sum ai*fi+r+p
1589 (do ((r (cons nil 0))
1590 (c (ring-unit ring))
1591 (division-count 0)
1592 (p f))
1593 ((or (poly-with-sugar-zerop p)
1594 (and top-reduction-only (not (poly-with-sugar-zerop r))))
1595 #+debug
1596 (progn
1597 (debug-cgb "~&~3T~d reduction~:p" division-count)
1598 (cond
1599 ((poly-with-sugar-zerop r)
1600 (debug-cgb " ---> 0"))))
1601 (values (poly-with-sugar-append (poly-with-sugar-nreverse r) p)
1602 division-count c))
1603 (declare (fixnum division-count) (integer c))
1604 (let ((i (position (poly-with-sugar-lm p) fl
1605 :test #'monom-divisible-by-p
1606 :key #'poly-with-sugar-lm)))
1607 (cond
1608 (i ;division possible
1609 (incf division-count)
1610 (let* ((g (nth i fl))
1611 (hash-tab (nth i cache))
1612 (gcd (funcall (ring-gcd ring) (poly-with-sugar-lc g) (poly-with-sugar-lc p)))
1613 (c1 (funcall (ring-/ ring) (poly-with-sugar-lc g) gcd))
1614 (c2 (funcall (ring-/ ring) (poly-with-sugar-lc p) gcd))
1615 (m (monom/ (poly-with-sugar-lm p) (poly-with-sugar-lm g))))
1616 ;; Multiply the equation c*f=sum ai*fi+r+p by c1.
1617 (setf r (scalar-times-poly-with-sugar c1 r ring)
1618 c (funcall (ring-* ring) c c1)
1619 p (scalar-times-poly-with-sugar c1 p ring)
1620 p (cached-poly-with-sugar-op p c2 m g pred ring hash-tab))))
1621 (t ;no division possible
1622 ;;move lt(p) to remainder
1623 (setf r (cons (cons (poly-with-sugar-lt p) (poly-with-sugar-poly r))
1624 (poly-with-sugar-sugar r))
1625 p (poly-with-sugar-tail p)))))))
1626
1627;; Parameter START is used when Grobner basis is calculated incrementally
1628;; and it signals that the elements of F from 0 to START-1 form a Grobner
1629;; basis already, so their pairs are not formed.
1630(defun cached-buchberger-with-sugar (F-no-sugar pred start top-reduction-only ring
1631 &aux (s (1- (length F-no-sugar))) B M F Cache)
1632 "Returns a Grobner basis of an ideal generated by a list of ordinary
1633polynomials F-NO-SUGAR. Adds initial sugar to the polynomials and
1634performs the Buchberger algorithm with ``sugar strategy''. It returns
1635an ordinary list of polynomials with no sugar. One of the most
1636effective algorithms for Grobner basis calculation."
1637 (declare (fixnum s))
1638 (unless (plusp s) (return-from cached-buchberger-with-sugar F-no-sugar)) ;cut startup costs
1639 #+debug (debug-cgb "~&GROBNER BASIS - BUCHBERGER WITH SUGER STRATEGY ALGORITHM")
1640 #+debug (when (plusp start) (debug-cgb "~&INCREMENTAL:~d done" start))
1641 #+grobner-check (when (plusp start)
1642 (grobner-test (subseq F-no-sugar 0 start)
1643 (subseq F-no-sugar 0 start) pred ring))
1644 (setf F (mapcar #'(lambda (x) (poly-add-sugar x ring)) F-no-sugar)
1645 B (nconc (makelist (list i j) (i 0 (1- start)) (j start s))
1646 (makelist (list i j) (i start (1- s)) (j (1+ i) s)))
1647 M (make-hash-table :test #'equal))
1648 ;;Initialize cache
1649 (dotimes (k (1+ s)) (push (make-hash-table :test #'equal) Cache))
1650 ;;Initialize treated pairs
1651 (dotimes (i (1- start))
1652 (do ((j (1+ i) (1+ j))) ((>= j start))
1653 (setf (gethash (list i j) M) t)))
1654 (setf B (buchberger-with-sugar-sort-pairs B F M pred ring))
1655 (do ((G F))
1656 ((endp B)
1657 (setf G (mapcar #'poly-with-sugar-poly G))
1658 ;;#+grobner-check(grobner-test G F-no-sugar pred ring)
1659 #+debug(debug-cgb "~&GROBNER END")
1660 G)
1661 (let ((pair (pop B)))
1662 (cond
1663 ((Criterion-1-with-sugar pair G))
1664 ((Criterion-2-with-sugar pair G M))
1665 (t
1666 (let ((SP (cached-normal-form-with-sugar
1667 (cons (cached-spoly (poly-with-sugar-poly (elt G (first pair)))
1668 (poly-with-sugar-poly (elt G (second pair)))
1669 pred ring
1670 (elt Cache (first pair))
1671 (elt Cache (second pair)))
1672 (third pair))
1673 G pred top-reduction-only ring Cache)))
1674 (cond
1675 ((poly-with-sugar-zerop SP))
1676 (t
1677 (setf s (1+ s)
1678 (poly-with-sugar-poly SP) (grobner-primitive-part
1679 (poly-with-sugar-poly SP) ring)
1680 (cdr (last G)) (list SP)
1681 (cdr (last Cache)) (list (make-hash-table :test #'equal))
1682 B (buchberger-with-sugar-merge-pairs B (makelist (list i s)
1683 (i 0 (1- s)))
1684 G M pred ring))
1685 #+debug (debug-cgb "~&[~d] Polynomials: ~d; Pairs left: ~d; Treated pairs: ~d"
1686 (third pair)
1687 (length G) (length B)
1688 (hash-table-count M)))))))
1689 (setf (cddr pair) nil
1690 (gethash pair M) t))))
1691
1692;; Implement f-term*g
1693(defun cached-poly-with-sugar-op (f c m g pred ring Cache)
1694 (poly-with-sugar- f (scalar-times-poly-with-sugar c (cached-monom-times-poly-with-sugar m g Cache) ring) pred ring))
1695
1696(defun cached-monom-times-poly-with-sugar (m f Cache)
1697 (cons
1698 (cached-monom-times-poly m (poly-with-sugar-poly f) Cache)
1699 (+ (poly-with-sugar-sugar f) (monom-sugar m))))
Note: See TracBrowser for help on using the repository browser.