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