close Warning: Can't synchronize with repository "(default)" (The repository directory has changed, you should resynchronize the repository with: trac-admin $ENV repository resync '(default)'). Look in the Trac log for more information.

source: branches/f4grobner/parse.lisp@ 645

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

* empty log message *

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