3 ;; Simple Maxima inteface to hompack routines
5 (in-package #-gcl
#:maxima
#+gcl
"MAXIMA")
7 (defmvar $debug_hompack nil
8 "Set to non-NIL to enable some debugging prints")
10 (defun parse-equations (eqnlist varlist fname
)
11 (let ((eqns (cdr eqnlist
))
17 ;; TODO: Check that varlist is a list of symbols.
19 ;; Process each equation
24 (unless ($polynomialp eqn varlist
)
25 (merror "~M: Is not a polynomial in ~M: ~M"
28 (let ((args (if (string-equal ($op eqn
) "+")
33 (push (length args
) numt
)
34 ;; TODO: Verify that eqn is a sum of terms.
36 ;; Process each term of the equation
42 (deg (mapcar #'(lambda (v)
43 ;; TODO: verify that V is a product
45 ;; For the term, determine the power
46 ;; of each variable and also create
47 ;; a product of the variable raised
48 ;; to the corresponding power.
49 (let ((p ($hipow term v
)))
51 ;; TODO: Check that p is non-negative integer
52 (setf prod
(mul prod
(power v p
)))
55 (c ($float
($expand
(div term prod
)))))
56 ;; Check that c is a real number since it's supposed
57 ;; to be the numerical coefficient of the polynomial term.
59 (merror "~M: coefficient of ~M is not a number: ~M"
62 (format t
"deg ~A~%" deg
)
64 (format t
"term deg ~A~%" term-deg
))
65 (push term-deg eqn-deg
)
66 ;; Accumulate these results for each term on a list.
68 (push (list* '(mlist) deg
) kdeg
)))
69 (setf total-deg
(* total-deg
(reduce #'max eqn-deg
)))
70 ;; Now accumlate the results from each equation on to the final list
71 (push (list* '(mlist) (nreverse kdeg
)) final-kdeg
)
72 (push (list* '(mlist) (nreverse coef
)) final-coef
)))
73 ;; Finally, return the full list of coefficients and degress for
74 ;; each term of each equation.
75 (setf final-kdeg
(nreverse final-kdeg
))
76 (setf final-coef
(nreverse final-coef
))
77 (setf numt
(nreverse numt
))
83 (defun convert-coef (coef)
84 (let* ((dim-j (length coef
))
85 ;;(dim-k (reduce #'max (mapcar #'$length coef)))
86 (dim-k (reduce #'max coef
:key
#'$length
))
87 (array (make-array (list dim-j dim-k
) :element-type
'double-float
))
88 (f2cl-array (make-array (* dim-j dim-k
) :element-type
'double-float
)))
90 (format t
"dim ~A ~A~%" dim-j dim-k
)
91 (format t
"array ~A~%" array
))
92 ;; F2CL maps multi-dimensional arrays into one-dimensional arrays
93 ;; in column-major order. That is, the order of indices is
95 (loop for eqn in coef for j from
1 do
96 (loop for term in
(cdr eqn
) for k from
1 do
98 (format t
"eqn ~A coef ~A = ~A~%" j k term
))
99 (setf (aref array
(1- j
) (1- k
)) ($float term
))
100 (setf (f2cl-lib::fref f2cl-array
(j k
) ((1 dim-j
) (1 dim-k
)))
103 (format t
"coef array ~A~%" array
))
106 (defun convert-kdeg (kdeg numt
)
107 (let* ((dim-j (length kdeg
))
109 (dim-k (reduce #'max numt
))
110 (array (make-array (list dim-j dim-l dim-k
) :element-type
'f2cl-lib
:integer4
))
111 (f2cl-array (make-array (* dim-j dim-l dim-k
) :element-type
'f2cl-lib
:integer4
)))
112 (loop for eqn in kdeg for j from
1 do
113 (loop for term in
(cdr eqn
) for l from
1 do
114 (loop for p in
(cdr term
) for k from
1 do
116 (format t
"set eqn ~A var ~A term ~A = ~A~%"
118 (setf (aref array
(1- j
) (1- k
) (1- l
)) p
)
119 (setf (f2cl-lib::fref f2cl-array
(j k l
) ((1 dim-j
) (1 dim-l
) (1 dim-k
))) p
))))
121 (format t
"kdeg array ~A~%" array
))
124 (defmfun $hompack_polsys
(eqnlist varlist
126 (iflg1 0) (epsbig 1d-4
) (epssml 1d-14
) (numrr 10)
128 "Solve the system of n polynomial equations in n unknowns.
130 EQNLIST list of polynomial equations. Must be in the form sum(c[k]*x1^p1*x2^p2*...*xn^pn)
131 VARLIST list of the n variables.
133 Returns a list with the following components
134 ifail Indicates results of the algorithm:
137 -3 - computed total deg is too small (shouldn't happen)
138 -4 - length of real work area is too small (shouldn't happen)
139 -5 - length of integer work area is too small (shouldn't happen)
140 -6 - if ifgl1 is not 00 or 01 or 10 or 11 (shouldn't happen)
141 0 - normal return (iflg2 list only contains 1)
142 1 - error (iflg2 list has values other than 1)
143 roots The roots of the system of equations
144 iflg2 How the path terminated
146 2 - specified error tolerance cannot be met. Increase epsbig
148 3 - maximum number of steps exceeded. Increase numrr.
149 However, the path may be diverging if the lambda value is
150 near 1 and the root values are large
151 4 - Jacobian matrix does not have full rank
152 5 - Tracking algorithm has lost the zero curve and is not making
153 progress. The error tolerances were too lenient.
154 6 - Normal flow Newton iteration failed to converge. The error
155 tolerance epsbig may be too stringent
156 7 - Illegal input parameters
157 lambda List of the final lambda (continuation) parameter
158 arclen List of the arc length of the patch for each root
159 nfe List of the number of Jacobian matrix evaluations required
162 Optional keywords args (key = val)
163 IFLG1 One of 0, 1, 10, 11. See docs for more info.
164 EPSBIG Local error tolerance allowed the path tracker
165 EPSSML Accuracy desired for final solution.
166 NUMRR Number of multiples of 1000 steps before abandoning path.
168 IFLG2 List indicating which paths to search. -2 means track this
169 path. Length must be the total degree of the equations.
170 SSPAR List of parameters used for optimal step size estimation. If
171 SSPAR[j] < 0, use default value. See Fortran polynf and
172 stepnf for more info."
174 (unless (= ($length eqnlist
) ($length varlist
))
175 (merror "~M: Number of equations (~M) is not the number of variables (~M)"
176 %%pretty-fname
(length eqnlist
) (length varlist
)))
177 (unless (and (listp varlist
) (eq (caar varlist
) 'mlist
))
178 (merror "~M: ~M is not a list of variables"
179 %%pretty-fname varlist
))
180 (unless (member iflg1
'(0 1 10 11))
181 (merror "~M: iflg1 must be 0, 1, 10, or 11. Got ~M"
182 %%pretty-fname iflg1
))
185 (unless (and sspar
(listp sspar
) (eq (caar sspar
) 'mlist
))
186 (merror "~M: sspar must be a list not ~M"
187 %%pretty-fname sspar
))
188 (unless (= ($length sspar
) 8)
189 (merror "~M: sspar must have length 8 not ~M"
190 %%pretty-fname
($length sspar
)))
191 (unless (every #'(lambda (x)
192 (typep ($float x
) 'double-float
))
195 (multiple-value-bind (total-deg kdeg coef numt
)
196 (parse-equations eqnlist varlist %%pretty-fname
)
198 (unless (= (length iflg2
) total-deg
)
199 (merror "~M: Length of iflg2 must be ~M not ~M"
200 %%pretty-fname total-deg
(length iflg2
)))
201 (unless (every #'integerp
(cdr iflg2
))
202 (merror "~M: iflg2 must be integers: ~M"
203 %%pretty-fname iflg2
)))
204 (let* ((n ($length eqnlist
))
205 (mmaxt (reduce #'max numt
))
206 (lenwk (+ 21 (* 61 n
) (* 10 n n
) (* 7 n mmaxt
) (* 4 n n mmaxt
)))
207 (wk (make-array lenwk
:element-type
'double-float
))
208 (leniwk (+ 43 (* 7 n
) (* n
(1+ n
) mmaxt
)))
209 (iwk (make-array lenwk
:element-type
'f2cl-lib
:integer4
))
210 (lamda (make-array total-deg
:element-type
'double-float
))
211 (arclen (make-array total-deg
:element-type
'double-float
))
212 (nfe (make-array total-deg
:element-type
'f2cl-lib
:integer4
))
213 (roots (make-array (* 2 (1+ n
) total-deg
) :element-type
'double-float
))
215 (make-array total-deg
:element-type
'f2cl-lib
:integer4
216 :initial-contents
(cdr iflg2
))
217 (make-array total-deg
:element-type
'f2cl-lib
:integer4
218 :initial-element -
2)))
220 (make-array 8 :element-type
'double-float
221 :initial-contents
(cdr ($float sspar
)))
222 (make-array 8 :element-type
'double-float
223 :initial-element -
1d0
)))
224 (coef-array (convert-coef coef
))
225 (kdeg-array (convert-kdeg kdeg numt
))
226 (numt (make-array (length numt
) :element-type
'f2cl-lib
:integer4
227 :initial-contents numt
)))
229 (format t
"coef-array ~A~%" coef-array
)
230 (format t
"kdeg-array ~A~%" kdeg-array
))
232 (multiple-value-bind (ignore-n ignore-numt ignore-coef-array ignore-kdeg-array
234 (hompack::polsys n numt coef-array kdeg-array iflg1 iflg2 epsbig epssml
235 sspar numrr n mmaxt total-deg lenwk leniwk
236 lamda roots arclen nfe wk iwk
)
237 (declare (ignore ignore-n ignore-numt ignore-coef-array ignore-kdeg-array
))
239 ;; Convert the roots into a list where each element of the
240 ;; list is a list of the form [x1=r1, x2=r2, ..., xn=rn].
243 ((maxify-roots (roots)
246 (loop for m from
1 to total-deg
249 (loop for j from
1 to n for var in
(cdr varlist
)
254 (add (f2cl-lib::fref roots
256 ((1 2) (1 (1+ n
)) (1 total-deg
)))
258 (f2cl-lib::fref roots
260 ((1 2) (1 (1+ n
)) (1 total-deg
))))))))))))
263 ;; Figure out if anything bad happened. If iflg1 is
264 ;; negative, just use it. Otherwise, check that iflg2
265 ;; Has a normal return for all values. If so, return
266 ;; 0. Otherwise return 1 to indicate that.
267 (cond ((minusp ret-iflg1
)
269 ((every #'(lambda (x) (= x
1)) iflg2
)
273 (r (maxify-roots roots
)))
278 (list* '(mlist) (coerce iflg2
'list
))
279 (list* '(mlist) (coerce lamda
'list
))
280 (list* '(mlist) (coerce arclen
'list
))
281 (list* '(mlist) (coerce nfe
'list
)))))))))
285 (defvar *fjac-fun
* nil
)
287 (in-package "HOMPACK")
289 ;; For HOMPACK_FIXPDF to evaluate the given function at the given
290 ;; point X, returning the values in V. The function is in *F-FUN*,
291 ;; computed by Maxima.
293 (declare (type (array double-float
(*)) v x
))
294 (f2cl-lib:with-multi-array-data
295 ((x cl
:double-float x-%data% x-%offset%
)
296 (v cl
:double-float v-%data% v-%offset%
))
297 (funcall maxima
::*f-fun
* x v
)
301 ;; For HOMPACK_FIXPDF to evaluate the k-th column of the Jacobian at
302 ;; the given point X, returning the values in V. The Jacobian is in
303 ;; *FJAC-FUN*, computed by Maxima.
305 (declare (type (f2cl-lib:integer4
) k
) (type (cl:array cl
:double-float
(*)) v x
))
306 (f2cl-lib:with-multi-array-data
307 ((x double-float x-%data% x-%offset%
)
308 (v double-float v-%data% v-%offset%
))
309 (funcall maxima
::*fjac-fun
* x v k
)
310 (values nil nil nil
)))
312 (in-package "MAXIMA")
314 (defmfun $hompack_fixpdf
(fcns varlist
316 (iflag -
1) (arctol -
1d0
) (eps 1d-5
) (trace 0) inita
)
319 (let* ((n (length (cdr varlist
)))
320 (y (make-array (1+ n
) :element-type
'double-float
))
322 (a (make-array ndima
:element-type
'double-float
))
323 (yp (make-array (1+ n
) :element-type
'double-float
))
324 (ypold (make-array (1+ n
) :element-type
'double-float
))
325 (qr (make-array (* n
(1+ n
)) :element-type
'double-float
))
326 (alpha (make-array n
:element-type
'double-float
))
327 (tz (make-array (1+ n
) :element-type
'double-float
))
328 (pivot (make-array (1+ n
) :element-type
'f2cl-lib
:integer4
))
329 (wt (make-array (1+ n
) :element-type
'double-float
))
330 (phi (make-array (* 16 (1+ n
)) :element-type
'double-float
))
331 (p (make-array (1+ n
) :element-type
'double-float
))
332 (par (make-array 1 :element-type
'double-float
))
333 (ipar (make-array 1 :element-type
'f2cl-lib
:integer4
))
336 (fvs (coerce-float-fun fcns varlist
))
337 (fj (let ((fj (meval `(($jacobian
) ,fcns
,varlist
))))
338 (mapcar #'(lambda (fjf)
339 (coerce-float-fun fjf varlist
))
340 ;; The Fortran code wants the k-th column, so
341 ;; transpose the Jacobian here to make the
342 ;; interface bewteen Maxima and Fortran a
343 ;; little simpler. Then we can just extract
344 ;; the k-th row of the transpose to get what's
346 (cdr ($transpose fj
)))))
349 ;; Compute the functions at the point X and return the
351 (declare (type (cl:array cl
:double-float
(*)) x v
))
352 (let* ((x-list (coerce x
'list
))
353 (v-list (apply fvs x-list
)))
354 (map-into v
#'identity
(cdr v-list
)))))
357 (declare (type (f2cl-lib:integer4
) k
) (type (cl:array cl
:double-float
(*)) v x
))
358 ;; Compute the k'th column of the Jacobian matrix of
359 ;; F(x) evaluated at X and store the result in V.
360 (let* ((x-list (coerce x
'list
))
361 (v-list (apply (elt fj
(1- k
)) x-list
)))
362 (map-into v
#'identity
(cdr v-list
))))))
365 (loop for ia in
(cdr inita
)
366 for k from
0 below
(length a
)
368 (let ((val ($float ia
)))
369 (setf (aref a k
) val
)
370 (setf (aref y
(1+ k
)) val
))))
371 (multiple-value-bind (ignore-n ignore-y
373 ignore-trace ignore-a ignore-ndima
375 arclen ignore-yp ignore-ypold ignore-qr ignore-alpha
376 ignore-tz ignore-pivot ignore-wt ignore-phi ignore-p
377 ignore-par ignore-ipar
)
378 (hompack::fixpdf n y iflag arctol eps trace a ndima nfe arclen yp ypold
379 qr alpha tz pivot wt phi p par ipar
)
380 (declare (ignore ignore-n ignore-y ignore-trace ignore-a ignore-ndima
381 ignore-yp ignore-ypold ignore-qr ignore-alpha
382 ignore-tz ignore-pivot ignore-wt ignore-phi ignore-p ignore-par
384 (let ((ans-y (list* '(mlist) (rest (coerce y
'list
)))))