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

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

* empty log message *

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