source: CGBLisp/doc/colored-poly.txt@ 1

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

First import of a version circa 1997.

File size: 18.6 KB
Line 
1
2;;; *COLORED-POLY-DEBUG* (nil) [VARIABLE]
3;;; If true debugging output is on.
4;;;
5;;; DEBUG-CGB (&rest args) [MACRO]
6;;;
7;;; MAKE-COLORED-POLY (poly k &key (key #'identity) [FUNCTION]
8;;; (main-order #'lex>) (parameter-order #'lex>)
9;;; &aux l)
10;;; Colored poly is represented as a list
11;;; (TERM1 TERM2 ... TERMS)
12;;; where each term is a triple
13;;; (MONOM . (POLY . COLOR))
14;;; where monoms and polys have common number of variables while color is
15;;; one of the three: :RED, :GREEN or :WHITE. This function translates
16;;; an ordinary polynomial into a colored one by dividing variables into
17;;; K and N-K, where N is the total number of variables in the polynomial
18;;; poly; the function KEY can be called to select variables in arbitrary
19;;; order.
20;;;
21;;; MAKE-COLORED-POLY-LIST (plist &rest rest) [FUNCTION]
22;;; Translate a list of polynomials PLIST into a list of colored
23;;; polynomials by calling MAKE-COLORED-POLY. Returns the resulting list.
24;;;
25;;; COLOR-POLY-LIST (flist &optional (cond (list nil nil))) [FUNCTION]
26;;; Add colors to an ordinary list of polynomials FLIST, according to a
27;;; condition COND. A condition is a pair of polynomial lists. Each
28;;; polynomial in COND is a polynomial in parameters only. The list
29;;; (FIRST COND) is called the ``green list'' and it consists of
30;;; polynomials which vanish for the parameters associated with the
31;;; condition. The list (SECOND COND) is called the ``red list
32;;;
33;;; COLOR-POLY (f &optional (cond (list nil nil))) [FUNCTION]
34;;; Add color to a single polynomial F, according to condition COND.
35;;; See the documentation of COLOR-POLY-LIST.
36;;;
37;;; COLORED-POLY-TO-POLY (cpoly) [FUNCTION]
38;;; For a given colored polynomial CPOLY, removes the colors and
39;;; it returns the polynomial as an ordinary polynomial with
40;;; coefficients which are polynomials in parameters.
41;;;
42;;; COLORED-POLY-PRINT (poly vars &key (stream t) (beg t) [FUNCTION]
43;;; (print-green-part nil)
44;;; (mark-coefficients nil))
45;;; Print a colored polynomial POLY. Use variables VARS to represent
46;;; the variables. Some of the variables are going to be used as
47;;; parameters, according to the length of the monomials in the main
48;;; monomial and coefficient part of each term in POLY. The key variable
49;;; STREAM may be used to redirect the output. If parameter
50;;; PRINT-GREEN-PART is set then the coefficients which have color :GREEN
51;;; will be printed, otherwise they are discarded silently. If
52;;; MARK-COEFFICIENTS is not NIL then every coefficient will be marked
53;;; according to its color, for instance G(U-1) would mean that U-1 is
54;;; in the green list. Returns P.
55;;;
56;;; COLORED-POLY-PRINT-LIST (poly-list vars &key (stream t) (beg t) [FUNCTION]
57;;; (print-green-part nil)
58;;; (mark-coefficients nil))
59;;; Pring a list of colored polynomials via a call to
60;;; COLORED-POLY-PRINT.
61;;;
62;;; DETERMINE (f &optional (cond (list nil nil)) (order #'lex>) [FUNCTION]
63;;; (ring *coefficient-ring*))
64;;; This function takes a list of colored polynomials F and a condition
65;;; COND, and it returns a list of pairs (COND' F') such that COND' cover
66;;; COND and F' is a ``determined'' version of the colored polynomial
67;;; list F, i.e. every polynomial has its leading coefficient determined.
68;;; This means that some of the initial coefficients in each polynomial
69;;; in F' are in the green list of COND, and the first non-green
70;;; coefficient is in the red list of COND. We note that F' differs from
71;;; F only by different colors: some of the terms marked :WHITE are now
72;;; marked either :GREEN or :RED. Coloring is done either by explicitly
73;;; checking membership in red or green list of COND, or implicitly by
74;;; performing Grobner basis calculations in the polynomial ring over the
75;;; parameters. The admissible monomial order ORDER is used only in the
76;;; parameter space. Also, the ring structure RING is used only for
77;;; calculations on polynomials of the parameters only.
78;;;
79;;; DETERMINE-1 (cond p end gp order ring) [FUNCTION]
80;;; Determine a single colored polynomial P according to condition COND.
81;;; Prepend green part GP to P. Cons the result with END, which should be
82;;; a list of colored polynomials, and return the resulting list of
83;;; polynomials. This is an auxillary function of DETERMINE.
84;;;
85;;; DETERMINE-WHITE-TERM (cond term restp end gp order ring) [FUNCTION]
86;;; This is an auxillary function of DETERMINE. In this function the
87;;; parameter COND is a condition. The parameters TERM, RESTP and GP are
88;;; three parts of a polynomial being processed, where TERM is colored
89;;; :WHITE. We test the membership in the red and green list of COND we
90;;; try to determine whether the term is :RED or :GREEN. This is done by
91;;; performing ideal membership tests in the polynomial ring. Let C be
92;;; the coefficient of TERM. Thus, C is a polynomial in parameters. We
93;;; find whether C is in the green list by performing a plain ideal
94;;; membership test. However, to test properly whether C is in the red
95;;; list, one needs a different strategy. In fact, we test whether
96;;; adding C to the red list would produce a non-empty set of parameters
97;;; in some algebraic extension. The test is whether 1 belongs to the
98;;; saturation ideal of (FIRST COND) in (CONS C (SECOND COND)). Thus, we
99;;; use POLY-SATURATION. If we are successful in determining the color of
100;;; TERM, we simply change the color of the term and return the list
101;;; ((COND P)) where P is obtained by appending GP, (LIST TERM) and
102;;; RESTP. If we cannot determine whether TERM is :RED or :GREEN, we
103;;; return the list ((COND' P') (COND'' P
104;;;
105;;; COND-SYSTEM-PRINT (system vars params &key (suppress-value t) [FUNCTION]
106;;; (print-green-part nil)
107;;; (mark-coefficients nil) &aux (label 0))
108;;; A conditional system SYSTEM is a list of pairs (COND PLIST), where
109;;; COND is a condition (a pair (GREEN-LIST RED-LIST)) and PLIST is a
110;;; list of colored polynomials. This function pretty-prints this list of
111;;; pairs. A conditional system is the data structure returned by
112;;; GROBNER-SYSTEM. This function returns SYSTEM, if SUPPRESS-VALUE is
113;;; non-NIL and no value otherwise. If MARK-COEFFICIENTS is non-NIL
114;;; coefficients will be marked as in G(u-1)*x+R(2)*y, which means that
115;;; u-1 is :GREEN and 2 is :RED.
116;;;
117;;; COND-PRINT (cond params) [FUNCTION]
118;;; Pretty-print a condition COND, using symbol list PARAMS as parameter
119;;; names.
120;;;
121;;; ADD-PAIRS (gs pred) [FUNCTION]
122;;; The parameter GS shoud be a Grobner system, i.e. a set of pairs
123;;; (CONDITION POLY-LIST) This functions adds the third component: the
124;;; list of initial critical pairs (I J), as in the ordinary Grobner
125;;; basis algorithm. In addition, it adds the length of of the POLY-LIST,
126;;; less 1, as the fourth component. The resulting list of quadruples is
127;;; returned.
128;;;
129;;; COND-PART (p) [FUNCTION]
130;;; Find the part of a colored polynomial P starting with the first
131;;; non-green term.
132;;;
133;;; COND-HM (p) [FUNCTION]
134;;; Return the conditional head monomial of a colored polynomial P.
135;;;
136;;; DELETE-GREEN-POLYS (gamma) [FUNCTION]
137;;; Delete totally green polynomials from in a grobner system GAMMA.
138;;;
139;;; GROBNER-SYSTEM (f &key (cover (list '(nil nil))) (main-order [FUNCTION]
140;;; #'lex>)
141;;; (parameter-order #'lex>) (reduce t)
142;;; (green-reduce t) (top-reduction-only nil)
143;;; (ring *coefficient-ring*)
144;;; &aux
145;;; (cover
146;;; (saturate-cover cover parameter-order ring))
147;;; (gamma
148;;; (delete-green-polys (mapcan #'(lambda (cond)
149;;; (determine f cond parameter-order ring))
150;;; cover))))
151;;; This function returns a grobner system, given a list of colored
152;;; polynomials F, Other parameters are:
153;;; A cover COVER, i.e. a list of conditions, i.e. pairs of the form
154;;; (GREEN-LIST RED-LIST), where GREEN-LIST and RED-LIST are to lists of
155;;; ordinary polynomials in parameters. A monomial order MAIN-ORDER used
156;;; on main variables (not parameters). A monomial order PARAMETER-ORDER
157;;; used in calculations with parameters only. REDUCE, a flag deciding
158;;; whether COLORED-REDUCTION will be performed on the resulting grobner
159;;; system. GREEN-REDUCE, a flag deciding whether the green list of each
160;;; condition will be reduced in a form of a reduced Grobner basis.
161;;; TOP-REDUCTION-ONLY, a flag deciding whether in the internal
162;;; calculations in the space of parameters top reduction only will be
163;;; used. RING, a structure as in the package COEFFICIENT-RING, used in
164;;; operations on the coefficients of the polynomials in parameters.
165;;;
166;;; REORDER-PAIRS (b bnew g pred &optional (sort-first nil)) [FUNCTION]
167;;; Reorder pairs according to some heuristic. The heuristic at this time
168;;; is ad hoc, in the future it should be replaced with sugar strategy
169;;; and a mechanism for implementing new heuristic strategies, as in the
170;;; GROBNER package.
171;;;
172;;; COLORED-CRITERION-1 (i j f) [FUNCTION]
173;;; Buchberger criterion 1 for colored polynomials.
174;;;
175;;; COLORED-CRITERION-2 (i j f b s) [FUNCTION]
176;;; Buchberger criterion 2 for colored polynomials.
177;;;
178;;; COND-NORMAL-FORM (f fl main-order parameter-order [FUNCTION]
179;;; top-reduction-only ring)
180;;; Returns the conditional normal form of a colored polynomial F with
181;;; respect to the list of colored polynomials FL. The list FL is assumed
182;;; to consist of determined polynomials, i.e. such that the first term
183;;; which is not marked :GREEN is :RED.
184;;;
185;;; COND-SPOLY (f g main-order parameter-order ring) [FUNCTION]
186;;; Returns the conditional S-polynomial of two colored polynomials F and
187;;; G. Both polynomials are assumed to be determined.
188;;;
189;;; COND-LM (f) [FUNCTION]
190;;; Returns the conditional leading monomial of a colored polynomial F,
191;;; which is assumed to be determined.
192;;;
193;;; COND-LC (f) [FUNCTION]
194;;; Returns the conditional leading coefficient of a colored polynomial
195;;; F, which is assumed to be determined.
196;;;
197;;; COLORED-TERM-TIMES-POLY (term f order ring) [FUNCTION]
198;;; Returns the product of a colored term TERM and a colored polynomial
199;;; F.
200;;;
201;;; COLORED-SCALAR-TIMES-POLY (c f ring) [FUNCTION]
202;;; Returns the product of an element of the coefficient ring C a colored
203;;; polynomial F.
204;;;
205;;; COLORED-TERM* (term1 term2 order ring) [FUNCTION]
206;;; Returns the product of two colored terms TERM1 and TERM2.
207;;;
208;;; COLOR* (c1 c2) [FUNCTION]
209;;; Returns a product of two colores. Rules:
210;;; :red * :red yields :red
211;;; any * :green yields :green
212;;; otherwise the result is :white.
213;;;
214;;; COLOR+ (c1 c2) [FUNCTION]
215;;; Returns a sum of colors. Rules:
216;;; :green + :green yields :green,
217;;; :red + :green yields :red
218;;; any other result is :white.
219;;;
220;;; COLOR- (c1 c2) [FUNCTION]
221;;; Identical to COLOR+.
222;;;
223;;; COLORED-POLY+ (p q main-order parameter-order ring) [FUNCTION]
224;;; Returns the sum of colored polynomials P and Q.
225;;;
226;;; COLORED-POLY- (p q main-order parameter-order ring) [FUNCTION]
227;;; Returns the difference of colored polynomials P and Q.
228;;;
229;;; COLORED-TERM-UMINUS (term ring) [FUNCTION]
230;;; Returns the negation of a colored term TERM.
231;;;
232;;; COLORED-MINUS-POLY (p ring) [FUNCTION]
233;;; Returns the negation of a colored polynomial P.
234;;;
235;;; STRING-GROBNER-SYSTEM (f vars params [FUNCTION]
236;;; &key (cover (list (list "[]" "[]")))
237;;; (main-order #'lex>)
238;;; (parameter-order #'lex>)
239;;; (ring *coefficient-ring*)
240;;; (suppress-value t)
241;;; (suppress-printing nil)
242;;; (mark-coefficients nil) (reduce t)
243;;; (green-reduce t)
244;;; &aux
245;;; (f
246;;; (parse-to-colored-poly-list f vars params
247;;; main-order parameter-order))
248;;; (cover
249;;; (string-cover cover params
250;;; parameter-order)))
251;;; An interface to GROBNER-SYSTEM in which polynomials can be specified
252;;; in infix notations as strings. Lists of polynomials are
253;;; comma-separated list marked by a matchfix operators []
254;;;
255;;; STRING-COND (cond params &optional (order #'lex>)) [FUNCTION]
256;;; Return the internal representation of a condition COND, specified
257;;; as pairs of strings (GREEN-LIST RED-LIST). GREEN-LIST and RED-LIST in
258;;; the input are assumed to be strings which parse to two lists of
259;;; polynomials with respect to variables whose names are in the list of
260;;; symbols PARAMS. ORDER is the predicate used to sort the terms of
261;;; the polynomials.
262;;;
263;;; STRING-COVER (cover params &optional (order #'lex>)) [FUNCTION]
264;;; Returns the internal representation of COVER, given in the form of
265;;; a list of conditions. See STRING-COND for description of a condition.
266;;;
267;;; SATURATE-COVER (cover order ring) [FUNCTION]
268;;; Brings every condition of a list of conditions COVER to the form (G
269;;; R) where G is saturated with respect to R and G is a Grobner basis
270;;; We could reduce R so that the elements of R are relatively prime,
271;;; but this is not currently done.
272;;;
273;;; SATURATE-COND (cond order ring) [FUNCTION]
274;;; Saturate a single condition COND. An auxillary function of
275;;; SATURATE-COVER.
276;;;
277;;; STRING-DETERMINE (f vars params &key (cond (quote ("[]" "[]"))) [FUNCTION]
278;;; (main-order #'lex>) (parameter-order #'lex>)
279;;; (suppress-value t) (suppress-printing nil)
280;;; (mark-coefficients nil)
281;;; (ring *coefficient-ring*)
282;;; &aux
283;;; (f
284;;; (parse-to-colored-poly-list f vars params
285;;; main-order parameter-order))
286;;; (cond
287;;; (string-cond cond params parameter-order)))
288;;; A string interface to DETERMINE. See the documentation of
289;;; STRING-GROBNER-SYSTEM.
290;;;
291;;; TIDY-GROBNER-SYSTEM (gs main-order parameter-order reduce [FUNCTION]
292;;; green-reduce ring)
293;;; Apply TIDY-PAIR to every pair of a Grobner system.
294;;;
295;;; TIDY-PAIR (pair main-order parameter-order reduce green-reduce [FUNCTION]
296;;; ring &aux gs)
297;;; Make the output of Grobner system more readable by performing
298;;; certain simplifications on an element of a Grobner system.
299;;; If REDUCE is non-NIL then COLORED-reduction will be performed.
300;;; In addition TIDY-COND is called on the condition part of the pair
301;;; PAIR.
302;;;
303;;; TIDY-COND (cond order ring) [FUNCTION]
304;;; Currently saturates condition COND and does RED-REDUCTION on the red
305;;; list.
306;;;
307;;; COLORED-REDUCTION (cond p main-order parameter-order ring [FUNCTION]
308;;; &aux (open (list (list cond nil p))) closed)
309;;; Reduce a list of colored polynomials P. The difficulty as compared
310;;; to the usual Buchberger algorithm is that the polys may have the same
311;;; leading monomial which may result in cancellations and polynomials
312;;; which may not be determined. Thus, when we find those, we will have
313;;; to split the condition by calling determine. Returns a list of pairs
314;;; (COND' P') where P' is a reduced grobner basis with respect to any
315;;; parameter choice compatible with condition COND'. Moreover, COND'
316;;; form a cover of COND.
317;;;
318;;; GREEN-REDUCE-COLORED-POLY (cond f parameter-order ring) [FUNCTION]
319;;; It takes a colored polynomial F and it returns a modified
320;;; polynomial obtained by reducing coefficient of F modulo green list of
321;;; the condition COND.
322;;;
323;;; GREEN-REDUCE-COLORED-LIST (cond fl parameter-order ring) [FUNCTION]
324;;; Apply GREEN-REDUCE-COLORED-POLY to a list of polynomials FL.
325;;;
326;;; COND-SYSTEM-GREEN-REDUCE (gs parameter-order ring) [FUNCTION]
327;;; Apply GREEN-REDUCE-COLORED-LIST to every pair of
328;;; a grobner system GS.
329;;;
330;;; PARSE-TO-COLORED-POLY-LIST (f vars params main-order [FUNCTION]
331;;; parameter-order
332;;; &aux (k (length vars)) (vars-params
333;;; (append vars params)))
334;;; Parse a list of polynomials F, given as a string, with respect to
335;;; a list of variables VARS, given as a list of symbols, to the internal
336;;; representation of a colored polynomial. The polynomials will be
337;;; properly sorted by MAIN-ORDER, with the coefficients, which are
338;;; polynomials in parameters, sorted by PARAMETER-ORDER. Both orders
339;;; must be admissible monomial orders. This form is suitable for parsing
340;;; polynomials with integer coefficients.
341;;;
342;;; RED-REDUCTION (p pred ring [FUNCTION]
343;;; &aux (p (remove-if #'poly-constant-p p)))
344;;; Takes a family of polynomials and produce a list whose prime factors
345;;; are the same but they are relatively prime
346;;; Repetitively used the following procedure: it finds two elements f, g
347;;; of P which are not relatively prime; it replaces f and g with
348;;; f/GCD(f,g), g/ GCD(f,f) and GCD(f,g).
349;;;
Note: See TracBrowser for help on using the repository browser.