source: CGBLisp/trunk/src/parse.lisp@ 102

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

Fixed parsing zero expressions.

File size: 11.9 KB
Line 
1;;; -*- Mode: Lisp; Syntax: Common-Lisp; Package: Grobner; Base: 10 -*-
2#|
3 *--------------------------------------------------------------------------*
4 | Copyright (C) 1994, Marek Rychlik (e-mail: rychlik@math.arizona.edu) |
5 | Department of Mathematics, University of Arizona, Tucson, AZ 85721 |
6 | |
7 | Everyone is permitted to copy, distribute and modify the code in this |
8 | directory, as long as this copyright note is preserved verbatim. |
9 *--------------------------------------------------------------------------*
10|#
11(defpackage "PARSE"
12 (:export parse parse-to-alist parse-string-to-alist
13 parse-to-sorted-alist parse-string-to-sorted-alist ^ [
14 poly-eval)
15 (:use "ORDER" "POLY" "COEFFICIENT-RING" "COMMON-LISP")
16 (:shadow sort-poly))
17
18(in-package "PARSE")
19
20(proclaim '(optimize (speed 0) (space 0) (safety 3) (debug 3)))
21
22;; The function PARSE yields the representations as above. The two functions
23;; PARSE-TO-ALIST and PARSE-STRING-TO-ALIST parse polynomials to the alist
24;; representations. For example
25;;
26;; >(parse)x^2-y^2+(-4/3)*u^2*w^3-5 --->
27;; (+ (* 1 (^ X 2)) (* -1 (^ Y 2)) (* -4/3 (^ U 2) (^ W 3)) (* -5))
28;;
29;; >(parse-to-alist '(x y u w))x^2-y^2+(-4/3)*u^2*w^3-5 --->
30;; (((0 0 2 3) . -4/3) ((0 2 0 0) . -1) ((2 0 0 0) . 1) ((0 0 0 0) . -5))
31;;
32;; >(parse-string-to-alist "x^2-y^2+(-4/3)*u^2*w^3-5" '(x y u w)) --->
33;; (((0 0 2 3) . -4/3) ((0 2 0 0) . -1) ((2 0 0 0) . 1) ((0 0 0 0) . -5))
34;;
35;; >(parse-string-to-alist "[x^2-y^2+(-4/3)*u^2*w^3-5,y]" '(x y u w))
36;; ([ (((0 0 2 3) . -4/3) ((0 2 0 0) . -1) ((2 0 0 0) . 1)
37;; ((0 0 0 0) . -5))
38;; (((0 1 0 0) . 1)))
39;; The functions PARSE-TO-SORTED-ALIST and PARSE-STRING-TO-SORTED-ALIST
40;; in addition sort terms by the predicate defined in the ORDER package
41;; For instance:
42;; >(parse-to-sorted-alist '(x y u w))x^2-y^2+(-4/3)*u^2*w^3-5
43;; (((2 0 0 0) . 1) ((0 2 0 0) . -1) ((0 0 2 3) . -4/3) ((0 0 0 0) . -5))
44;; >(parse-to-sorted-alist '(x y u w) t #'grlex>)x^2-y^2+(-4/3)*u^2*w^3-5
45;; (((0 0 2 3) . -4/3) ((2 0 0 0) . 1) ((0 2 0 0) . -1) ((0 0 0 0) . -5))
46
47;;(eval-when (compile)
48;; (proclaim '(optimize safety)))
49
50(defun convert-number (number-or-poly n)
51 "Returns NUMBER-OR-POLY, if it is a polynomial. If it is a number,
52it converts it to the constant monomial in N variables. If the result
53is a number then convert it to a polynomial in N variables."
54 (if (numberp number-or-poly)
55 (list (cons (make-list n :initial-element 0) number-or-poly))
56 number-or-poly))
57
58(defun $poly+ (p q n order ring)
59 "Add two polynomials P and Q, where each polynomial is either a
60numeric constant or a polynomial in internal representation. If the
61result is a number then convert it to a polynomial in N variables."
62 (poly+ (convert-number p n) (convert-number q n) order ring))
63
64(defun $poly- (p q n order ring)
65 "Subtract two polynomials P and Q, where each polynomial is either a
66numeric constant or a polynomial in internal representation. If the
67result is a number then convert it to a polynomial in N variables."
68 (poly- (convert-number p n) (convert-number q n) order ring))
69
70(defun $minus-poly (p n ring)
71 "Negation of P is a polynomial is either a numeric constant or a
72polynomial in internal representation. If the result is a number then
73convert it to a polynomial in N variables."
74 (minus-poly (convert-number p n) ring))
75
76(defun $poly* (p q n order ring)
77 "Multiply two polynomials P and Q, where each polynomial is either a
78numeric constant or a polynomial in internal representation. If the
79result is a number then convert it to a polynomial in N variables."
80 (poly* (convert-number p n) (convert-number q n) order ring))
81
82(defun $poly/ (p q ring)
83 "Divide a polynomials P which is either a numeric constant or a
84polynomial in internal representation, by a number Q."
85 (if (numberp p)
86 (common-lisp:/ p q)
87 (scalar-times-poly (common-lisp:/ q) p ring)))
88
89(defun $poly-expt (p l n order ring)
90 "Raise polynomial P, which is a polynomial in internal
91representation or a numeric constant, to power L. If P is a number,
92convert the result to a polynomial in N variables."
93 (poly-expt (convert-number p n) l order ring))
94
95(defun parse (&optional stream)
96 "Parser of infis expressions with integer/rational coefficients
97The parser will recognize two kinds of polynomial expressions:
98
99- polynomials in fully expanded forms with coefficients
100 written in front of symbolic expressions; constants can be optionally
101 enclosed in (); for example, the infix form
102 X^2-Y^2+(-4/3)*U^2*W^3-5
103 parses to
104 (+ (- (EXPT X 2) (EXPT Y 2)) (* (- (/ 4 3)) (EXPT U 2) (EXPT W 3)) (- 5))
105
106- lists of polynomials; for example
107 [X-Y, X^2+3*Z]
108 parses to
109 (:[ (- X Y) (+ (EXPT X 2) (* 3 Z)))
110 where the first symbol [ marks a list of polynomials.
111
112-other infix expressions, for example
113 [(X-Y)*(X+Y)/Z,(X+1)^2]
114parses to:
115 (:[ (/ (* (- X Y) (+ X Y)) Z) (EXPT (+ X 1) 2))
116Currently this function is implemented using M. Kantrowitz's INFIX package."
117 (read-from-string
118 (concatenate 'string
119 "#I("
120 (with-output-to-string (s)
121 (loop
122 (multiple-value-bind (line eof)
123 (read-line stream t)
124 (format s "~A" line)
125 (when eof (return)))))
126 ")")))
127
128;; Translate output from parse to a pure list form
129;; assuming variables are VARS
130
131(defun alist-form (plist vars)
132 "Translates an expression PLIST, which should be a list of polynomials
133in variables VARS, to an alist representation of a polynomial.
134It returns the alist. See also PARSE-TO-ALIST."
135 (cond
136 ((endp plist) nil)
137 ((eql (first plist) '[)
138 (cons '[ (mapcar #'(lambda (x) (alist-form x vars)) (rest plist))))
139 (t
140 (assert (eql (car plist) '+))
141 (alist-form-1 (rest plist) vars))))
142
143(defun alist-form-1 (p vars
144 &aux (ht (make-hash-table
145 :test #'equal :size 16))
146 stack)
147 (dolist (term p)
148 (assert (eql (car term) '*))
149 (incf (gethash (powers (cddr term) vars) ht 0) (second term)))
150 (maphash #'(lambda (key value) (unless (zerop value)
151 (push (cons key value) stack))) ht)
152 stack)
153
154(defun powers (monom vars
155 &aux (tab (pairlis vars (make-list (length vars)
156 :initial-element 0))))
157 (dolist (e monom (mapcar #'(lambda (v) (cdr (assoc v tab))) vars))
158 (assert (equal (first e) '^))
159 (assert (integerp (third e)))
160 (assert (= (length e) 3))
161 (let ((x (assoc (second e) tab)))
162 (if (null x) (error "Variable ~a not in the list of variables."
163 (second e))
164 (incf (cdr x) (third e))))))
165
166
167;; New implementation based on the INFIX package of Mark Kantorowitz
168(defun parse-to-alist (vars &optional stream)
169 "Parse an expression already in prefix form to an association list form
170according to the internal CGBlisp polynomial syntax: a polynomial is an
171alist of pairs (MONOM . COEFFICIENT). For example:
172 (WITH-INPUT-FROM-STRING (S \"X^2-Y^2+(-4/3)*U^2*W^3-5\")
173 (PARSE-TO-ALIST '(X Y U W) S))
174evaluates to
175(((0 0 2 3) . -4/3) ((0 2 0 0) . -1) ((2 0 0 0) . 1) ((0 0 0 0) . -5))"
176 (poly-eval (parse stream) vars))
177
178
179(defun parse-string-to-alist (str vars)
180 "Parse string STR and return a polynomial as a sorted association
181list of pairs (MONOM . COEFFICIENT). For example:
182(parse-string-to-alist \"[x^2-y^2+(-4/3)*u^2*w^3-5,y]\" '(x y u w))
183 ([ (((0 0 2 3) . -4/3) ((0 2 0 0) . -1) ((2 0 0 0) . 1)
184 ((0 0 0 0) . -5))
185 (((0 1 0 0) . 1)))
186The functions PARSE-TO-SORTED-ALIST and PARSE-STRING-TO-SORTED-ALIST
187sort terms by the predicate defined in the ORDER package."
188 (with-input-from-string (stream str)
189 (parse-to-alist vars stream)))
190
191
192(defun parse-to-sorted-alist (vars &optional (order #'lex>) (stream t))
193 "Parses streasm STREAM and returns a polynomial represented as
194a sorted alist. For example:
195(WITH-INPUT-FROM-STRING (S \"X^2-Y^2+(-4/3)*U^2*W^3-5\")
196 (PARSE-TO-SORTED-ALIST '(X Y U W) S))
197returns
198(((2 0 0 0) . 1) ((0 2 0 0) . -1) ((0 0 2 3) . -4/3) ((0 0 0 0) . -5))
199and
200(WITH-INPUT-FROM-STRING (S \"X^2-Y^2+(-4/3)*U^2*W^3-5\")
201 (PARSE-TO-SORTED-ALIST '(X Y U W) T #'GRLEX>) S)
202returns
203(((0 0 2 3) . -4/3) ((2 0 0 0) . 1) ((0 2 0 0) . -1) ((0 0 0 0) . -5))"
204 (sort-poly (parse-to-alist vars stream) order))
205
206(defun parse-string-to-sorted-alist (str vars &optional (order #'lex>))
207 "Parse a string to a sorted alist form, the internal representation
208of polynomials used by our system."
209 (with-input-from-string (stream str)
210 (parse-to-sorted-alist vars order stream)))
211
212(defun sort-poly-1 (p order)
213 "Sort the terms of a single polynomial P using an admissible monomial order ORDER.
214Returns the sorted polynomial. Destructively modifies P."
215 (sort p order :key #'first))
216
217;; Sort a polynomial or polynomial list
218(defun sort-poly (poly-or-poly-list &optional (order #'lex>))
219 "Sort POLY-OR-POLY-LIST, which could be either a single polynomial
220or a list of polynomials in internal alist representation, using
221admissible monomial order ORDER. Each polynomial is sorted using
222SORT-POLY-1."
223 (cond
224 ((eql poly-or-poly-list :syntax-error) nil)
225 ((null poly-or-poly-list) nil)
226 ((eql (car poly-or-poly-list) '[)
227 (cons '[ (mapcar #'(lambda (p) (sort-poly-1 p order))
228 (rest poly-or-poly-list))))
229 (t (sort-poly-1 poly-or-poly-list order))))
230
231(defun poly-eval-1 (expr vars order ring
232 &aux
233 (n (length vars))
234 (basis (monom-basis (length vars))))
235 "Evaluate an expression EXPR as polynomial by substituting operators
236+ - * expt with corresponding polynomial operators and variables VARS
237with monomials (1 0 ... 0), (0 1 ... 0) etc. We use special versions
238of binary operators $poly+, $poly-, $minus-poly, $poly* and $poly-expt
239which work like the corresponding functions in the POLY package, but
240accept scalars as arguments as well."
241 (cond
242 ((numberp expr)
243 (cond
244 ((zerop expr) NIL)
245 (t (list (cons (make-list n :initial-element 0) expr)))))
246 ((symbolp expr)
247 (nth (position expr vars) basis))
248 ((consp expr)
249 (case (car expr)
250 (expt
251 (if (= (length expr) 3)
252 ($poly-expt (poly-eval-1 (cadr expr) vars order ring)
253 (caddr expr)
254 n order ring)
255 (error "Too many arguments to EXPT")))
256 (/
257 (if (and (= (length expr) 3)
258 (numberp (caddr expr)))
259 ($poly/ (cadr expr) (caddr expr) ring)
260 (error "The second argument to / must be a number")))
261 (otherwise
262 (let ((r (mapcar
263 #'(lambda (e) (poly-eval-1 e vars order ring))
264 (cdr expr))))
265 (ecase (car expr)
266 (+ (reduce #'(lambda (p q) ($poly+ p q n order ring)) r))
267 (-
268 (if (endp (cdr r))
269 ($minus-poly (car r) n ring)
270 ($poly- (car r)
271 (reduce #'(lambda (p q) ($poly+ p q n order ring)) (cdr r))
272 n
273 order ring)))
274 (*
275 (reduce #'(lambda (p q) ($poly* p q n order ring)) r))
276 )))))))
277
278
279(defun poly-eval (expr vars &optional (order #'lex>) (ring *coefficient-ring*))
280 "Evaluate an expression EXPR, which should be a polynomial
281expression or a list of polynomial expressions (a list of expressions
282marked by prepending keyword :[ to it) given in lisp prefix notation,
283in variables VARS, which should be a list of symbols. The result of
284the evaluation is a polynomial or a list of polynomials (marked by
285prepending symbol '[) in the internal alist form. This evaluator is
286used by the PARSE package to convert input from strings directly to
287internal form."
288 (cond
289 ((numberp expr)
290 (unless (zerop expr)
291 (list (cons (make-list (length vars) :initial-element 0) expr))))
292 ((or (symbolp expr) (not (eq (car expr) :[)))
293 (poly-eval-1 expr vars order ring))
294 (t (cons '[ (mapcar #'(lambda (p) (poly-eval-1 p vars order ring)) (rest expr))))))
295
296
297;; Return the standard basis of the monomials in n variables
298(defun monom-basis (n &aux
299 (basis
300 (copy-tree
301 (make-list n :initial-element
302 (list (cons
303 (make-list
304 n
305 :initial-element 0)
306 1))))))
307 "Generate a list of monomials ((1 0 ... 0) (0 1 0 ... 0) ... (0 0 ... 1)
308which correspond to linear monomials X1, X2, ... XN."
309 (dotimes (i n basis)
310 (setf (elt (caar (elt basis i)) i) 1)))
Note: See TracBrowser for help on using the repository browser.