More documentation and comment out debugging print.
[maxima.git] / src / plot.lisp
blob0e52388506524231b82ad59575e5a2659b125b24
1 ;;Copyright William F. Schelter 1990, All Rights Reserved
2 ;;
3 ;; Time-stamp: "2024-03-26 21:44:42 villate"
5 (in-package :maxima)
7 (defvar $mgnuplot_command "mgnuplot")
8 (defvar $geomview_command "geomview")
9 (defvar $xmaxima_plot_command "xmaxima")
12 Examples
14 /* plot of z^(1/3)...*/
15 plot3d(r^.33*cos(th/3),[r,0,1],[th,0,6*%pi],['grid,12,80],['transform_xy,polar_to_xy],['plot_format,geomview]);
17 /* plot of z^(1/2)...*/
18 plot3d(r^.5*cos(th/2),[r,0,1],[th,0,6*%pi],['grid,12,80],['transform_xy,polar_to_xy],['plot_format,xmaxima]);
20 /* moebius */
21 plot3d([cos(x)*(3+y*cos(x/2)),sin(x)*(3+y*cos(x/2)),y*sin(x/2)],[x,-%pi,%pi],[y,-1,1],['grid,50,15]);
23 /* klein bottle */
24 plot3d([5*cos(x)*(cos(x/2)*cos(y)+sin(x/2)*sin(2*y)+3.0) - 10.0,
25 -5*sin(x)*(cos(x/2)*cos(y)+sin(x/2)*sin(2*y)+3.0),
26 5*(-sin(x/2)*cos(y)+cos(x/2)*sin(2*y))],[x,-%pi,%pi],[y,-%pi,%pi],
27 ['grid,40,40]);
28 /* torus */
29 plot3d([cos(y)*(10.0+6*cos(x)), sin(y)*(10.0+6*cos(x)),-6*sin(x)],
30 [x,0,2*%pi],[y,0,2*%pi],['grid,40,40]);
33 ;; Each plot is described by an object whose class depends on the
34 ;; graphic program used to visualize it (option "plot_format").
35 ;; We currently have 3 classes for Gnuplot, Xmaxima and Geomview
37 (defclass gnuplot-plot ()
38 ((data :initarg :data :initform "")
39 (pipe :initarg :pipe :initform nil)))
41 (defclass xmaxima-plot ()
42 ((data :initarg :data :initform "")
43 (pipe :initarg :pipe :initform nil)))
45 (defclass geomview-plot ()
46 ((data :initarg :data :initform "")
47 (pipe :initarg :pipe :initform nil)))
49 ;; These are the methods that each plot class should define.
50 ;; For each class (plot plot_format) there is a corresponding file
51 ;; plot_format_def.lisp
52 ;; where those methods are defined for the particular class.
54 (defgeneric plot-preamble (plot options)
55 (:documentation "Plots the preamble for a plot."))
57 (defgeneric plot2d-command (plot fun options range)
58 (:documentation "Writes the command that creates a plot."))
60 (defgeneric plot3d-command (plot functions options titles)
61 (:documentation "Writes the command that creates a plot."))
63 (defgeneric plot-shipout (plot options &optional output-file)
64 (:documentation "Sends the plot commands to the graphic program."))
66 ;; Convenience functions used to check values of plot arguments and options
68 (defun ensure-string (x)
69 (cond
70 ((stringp x) x)
71 ((symbolp x) (print-invert-case (stripdollar x)))
72 (t (maybe-invert-string-case (string (implode (strgrind x)))))))
74 (defmfun $join (x y)
75 (if (and ($listp x) ($listp y))
76 (cons '(mlist) (loop for w in (cdr x) for u in (cdr y) collect w collect u))
77 (merror (intl:gettext "join: both arguments must be lists."))))
79 (defun coerce-float (x) ($float (meval* x)))
81 ;; This variable seems to be a remnant of when Maxima was distributed with
82 ;; two plotting programs: mgnuplot and omplotdata. omplotdata no longer
83 ;; exists and the only program left in the directory *maxima-plotdir* is
84 ;; a version of mgnuplot that is no longer usable.
85 ;; Let's leave it for now, in case we ever recover mgnuplot (to get rid
86 ;; of it would imply modifying init-cl.lisp when this variable is set.
87 (defvar *maxima-plotdir* "")
89 ;; *ROT* AND FRIENDS ($ROT, $ROTATE_PTS, $ROTATE_LIST) CAN PROBABLY GO AWAY !!
90 ;; THEY ARE UNDOCUMENTED AND UNUSED !!
91 ;; (defvar *rot* (make-array 9 :element-type 'flonum))
92 ;; (defvar $rot nil)
94 ;; Global plot options list; this is a property list.. It is not a
95 ;; Maxima variable, to discourage users from changing it directly; it
96 ;; should be changed via set_plot_option
98 (defvar *plot-options*
99 '($plot_format $gnuplot_pipes
100 $grid (30 30) $run_viewer t $axes t
101 ;; With adaptive plotting, 29 nticks should be enough; adapt_depth
102 ;; controls the number of splittings adaptive-plotting will do.
103 $nticks 29 $adapt_depth 5
104 $color ($blue $red $green $magenta $black $cyan)
105 $point_type ($bullet $box $triangle $plus $times $asterisk)
106 $palette (((mlist) $hue 0.33333333 0.7 1 0.5)
107 ((mlist) $hue 0.8 0.7 1 0.4))
108 $gnuplot_svg_background "white"
109 $gnuplot_preamble "" $gnuplot_term $default))
111 ;; Apparently Wxmaxima needs a default plot_options Maxima list pre-defined.
112 ;; We will then create such list with minimum content.
113 ;; (TO-DO: check whether recent versions of Wxmaxima still require that)
115 (defvar $plot_options
116 '((mlist) ((mlist) $plot_format $gnuplot_pipes)))
118 ;; $plot_realpart option is false by default but *plot-realpart* is true
119 ;; because coerce-float-fun is used outside of plot package too.
120 (defvar *plot-realpart* t)
122 (defun maybe-realpart (x)
123 (if *plot-realpart*
124 ($realpart x)
125 (if (zerop1 ($imagpart x))
126 ($realpart x)
127 nil)))
129 ;; gnuplot_pipes functions. They allow the use of Gnuplot through a
130 ;; pipe in order to keep it active (this makes it possible for instance,
131 ;; to rotate a 3d surface with the mouse)
133 (defvar *missing-data-indicator* "NaN")
135 (defvar *gnuplot-stream* nil)
136 (defvar *gnuplot-command* "")
138 (defvar $gnuplot_command "gnuplot")
140 (defun start-gnuplot-process (path)
141 ;; TODO: Forward gnuplot's stderr stream to maxima's stderr output
142 #+clisp (setq *gnuplot-stream* (ext:make-pipe-output-stream path))
143 ;; TODO: Forward gnuplot's stderr stream to maxima's stderr output
144 #+lispworks (setq *gnuplot-stream* (system:open-pipe path))
145 #+cmu (setq *gnuplot-stream*
146 (ext:process-input (ext:run-program path nil :input :stream
147 :output *error-output* :wait nil)))
148 #+scl (setq *gnuplot-stream*
149 (ext:process-input (ext:run-program path nil :input :stream
150 :output *error-output* :wait nil)))
151 #+sbcl (setq *gnuplot-stream*
152 (sb-ext:process-input (sb-ext:run-program path nil
153 :input :stream
154 :output *error-output* :wait nil
155 :search t)))
156 #+gcl (setq *gnuplot-stream*
157 (open (concatenate 'string "| " path) :direction :output))
158 #+ecl (progn
159 (setq *gnuplot-stream* (ext:run-program path nil :input :stream :output *error-output* :error :output :wait nil)))
160 #+ccl (setf *gnuplot-stream*
161 (ccl:external-process-input-stream
162 (ccl:run-program path nil
163 :wait nil :output *error-output*
164 :input :stream)))
165 #+allegro (setf *gnuplot-stream* (excl:run-shell-command
166 path :input :stream :output *error-output* :wait nil))
167 #+abcl (setq *gnuplot-stream* (system::process-input (system::run-program path nil :wait nil)))
168 #-(or clisp cmu sbcl gcl scl lispworks ecl ccl allegro abcl)
169 (merror (intl:gettext "plotting: I don't know how to tell this Lisp to run Gnuplot."))
171 (if (null *gnuplot-stream*)
172 (merror (intl:gettext "plotting: I tried to execute ~s but *GNUPLOT-STREAM* is still null.~%") path))
174 ;; set mouse must be the first command send to gnuplot
175 (send-gnuplot-command "set mouse"))
177 (defun check-gnuplot-process ()
178 (if (null *gnuplot-stream*)
179 (start-gnuplot-process $gnuplot_command)))
181 (defmfun $gnuplot_close ()
182 (stop-gnuplot-process)
185 (defmfun $gnuplot_start ()
186 (check-gnuplot-process)
189 (defmfun $gnuplot_restart ()
190 ($gnuplot_close)
191 ($gnuplot_start))
193 (defmfun $gnuplot_send (command)
194 (send-gnuplot-command command))
196 (defun stop-gnuplot-process ()
197 (unless (null *gnuplot-stream*)
198 (progn
199 (close *gnuplot-stream*)
200 (setq *gnuplot-stream* nil))))
202 (defun send-gnuplot-command (command &optional recursive)
203 (if (null *gnuplot-stream*)
204 (start-gnuplot-process $gnuplot_command))
205 (handler-case (unless (null command)
206 (format *gnuplot-stream* "~a ~%" command)
207 (finish-output *gnuplot-stream*))
208 (error (e)
209 ;; allow gnuplot to restart if stream-error, or just an error is signaled
210 ;; only try to restart once, to prevent an infinite loop
211 (cond (recursive
212 (error e))
214 (warn "~a~%Trying new stream.~%" e)
215 (setq *gnuplot-stream* nil)
216 (send-gnuplot-command command t))))))
218 (defmfun $gnuplot_reset ()
219 (send-gnuplot-command "unset output")
220 (send-gnuplot-command "reset"))
222 (defmfun $gnuplot_replot (&optional s)
223 (if (null *gnuplot-stream*)
224 (merror (intl:gettext "gnuplot_replot: Gnuplot is not running.")))
225 (cond ((null s)
226 (send-gnuplot-command "replot"))
227 ((stringp s)
228 (send-gnuplot-command s)
229 (send-gnuplot-command "replot"))
231 (merror (intl:gettext "gnuplot_replot: argument, if present, must be a string; found: ~M") s)))
234 ;; PLOT OPTIONS PARSING
236 ;; allow this to be set in a system init file (sys-init.lsp)
237 ;; (villate 20240322: I don't understand that comment)
239 (defmfun $get_plot_option (&optional name n)
240 (let (options)
241 ;; Converts the options property list into a Maxima list
242 (do* ((list (copy-tree *plot-options*) (cddr list))
243 (key (first list) (first list))
244 (value (second list) (second list)))
245 ((endp list))
246 (if (consp value)
247 (push (cons '(mlist) (cons key value)) options)
248 (push (list '(mlist) key value) options)))
249 (setf options (cons '(mlist) (nreverse options)))
250 (if name
251 (let ((value (find name (cdr options) :key #'second)))
252 (if n
253 (nth n value)
254 value))
255 options)))
257 (defun quote-strings (opt)
258 (if (atom opt)
259 (if (stringp opt)
260 (format nil "~s" opt)
261 opt)
262 (cons (quote-strings (car opt))
263 (quote-strings (cdr opt)))))
265 (defun get-plot-option-string (option &optional (index 1))
266 (let* ((val ($get_plot_option option 2))
267 (val-list (if ($listp val)
268 (cdr val)
269 `(,val))))
270 (ensure-string (nth (mod (- index 1) (length val-list)) val-list))))
272 (defmfun $set_plot_option (&rest value)
273 (setq *plot-options* (plot-options-parser value *plot-options*))
274 ($get_plot_option))
276 ;; Removes option "name" from current plotting options
277 (defmfun $remove_plot_option (name)
278 (remf *plot-options* name))
280 (defun get-gnuplot-term (term)
281 (let* ((sterm (string-downcase (ensure-string term)))
282 (pos (search " " sterm)))
283 (if pos
284 (subseq sterm 0 pos)
285 sterm)))
286 ;; end of PLOT OPTIONS parsing functions
288 (defvar $pstream nil)
290 (defun print-pt1 (f str)
291 (if (floatp f)
292 (format str "~,,,,,,'eg " f)
293 (format str "~a " *missing-data-indicator*)))
295 (defstruct (polygon (:type list)
296 (:constructor %make-polygon (pts edges)))
297 (dummy '($polygon simp))
298 pts edges)
300 (eval-when
301 (:compile-toplevel :execute)
303 (defmacro z-pt (ar i) `(aref ,ar (the fixnum (+ 2 (* ,i 3)))))
304 (defmacro y-pt (ar i) `(aref ,ar (the fixnum (1+ (* ,i 3)))))
305 (defmacro x-pt (ar i) `(aref ,ar (the fixnum (* ,i 3))))
306 (defmacro rot (m i j) `(aref ,m (the fixnum (+ ,i (the fixnum (* 3 ,j))))))
308 (defmacro print-pt (f)
309 `(print-pt1 ,f $pstream ))
311 (defmacro make-polygon (a b)
312 `(list '($polygon) ,a ,b)))
314 (defun draw3d (f minx maxx miny maxy nxint nyint)
315 (let* ((epsx (/ (- maxx minx) nxint))
316 (x 0.0) ( y 0.0)
317 (epsy (/ (- maxy miny) nyint))
318 (nx (+ nxint 1))
319 (l 0)
320 (ny (+ nyint 1))
321 (ar (make-array (+ 12 ; 12 for axes
322 (* 3 nx ny)) :fill-pointer (* 3 nx ny)
323 :element-type t :adjustable t)))
324 (declare (type flonum x y epsy epsx)
325 (fixnum nx ny l)
326 (type (cl:array t) ar))
327 (loop for j below ny
328 initially (setq y miny)
329 do (setq x minx)
330 (loop for i below nx
332 (setf (x-pt ar l) x)
333 (setf (y-pt ar l) y)
334 (setf (z-pt ar l) (funcall f x y))
335 (incf l)
336 (setq x (+ x epsx))
338 (setq y (+ y epsy)))
339 (make-polygon ar (make-grid-vertices nxint nyint))))
341 ;; ***** This comment refers to some unexistent function make-vertices ****
342 ;; ***** let's leave it here for the sake of history :) ****
343 ;; The following is 3x2 = 6 rectangles
344 ;; call (make-vertices 3 2)
345 ;; there are 4x3 = 12 points.
346 ;; ordering is x0,y0,z0,x1,y1,z1,....,x11,y11,z11
347 ;; ----
348 ;; ||||
349 ;; ----
350 ;; ||||
351 ;; ----
353 ;; make-grid-vertices
354 ;; Creates an array that describes a rectangular grid with nx intervals
355 ;; in the x direction and ny intervals in the y direction.
356 ;; Such grid is then formed by nx*ny rectangles.
357 ;; Each rectangle is defined by four points and a value of zero, which
358 ;; will be later replaced by the z value corresponding to that rectangle.
360 ;; Thus, each sequence of 5 integers in the resulting array describe
361 ;; a rectangle in the grid. For instance, 0 3 4 1 0 corresponds to the
362 ;; the rectangle with vertices at the points with indices 0 3 4 and 1.
363 ;; The points on the top row of the grid have indices:
364 ;; 0 1 2 ... nx
365 ;; and the points in the j'th row from the top (counting from 0) are:
366 ;; j j+1 j+2 ... j+nx
367 ;; The order of the points given for each rectangle gives the correct
368 ;; sequence when the boundary of the rectangle is traversed in
369 ;; the clockwise direction.
371 (defun make-grid-vertices (nx ny)
372 (declare (fixnum nx ny))
373 (let* ((tem (make-array (+ 15 (* 5 nx ny)) :fill-pointer (* 5 nx ny)
374 :adjustable t
375 :element-type '(mod #x80000000)))
376 (m nx )
377 (nxpt (+ nx 1))
378 (i 0)
380 (declare (fixnum i nxpt m)
381 (type (cl:array (mod #x80000000)) tem))
382 (loop for k below (length tem)
384 (setf (aref tem k) i)
385 (setf (aref tem (incf k))
386 (+ nxpt i))
387 (setf (aref tem (incf k))
388 (+ nxpt (incf i )))
389 (setf (aref tem (incf k)) i)
390 (setf (aref tem (incf k)) 0) ;place for max
391 (setq m (- m 1))
392 (cond ((eql m 0)
393 (setq m nx)
394 (setq i (+ i 1))))
396 tem))
398 ;; $rotation1
399 ;; The argument phi is elevation and th is azimuth. This function returns the
400 ;; matrix of a rotation in the positive direction (from x to y) along
401 ;; the z axis, with an angle equal to the azimuth, followed by a negative
402 ;; rotation (from x to z) along the new y axis, with an angle equal to
403 ;; the elevation. Even though it is declared as a Maxima function, it can
404 ;; not be called with symbolic arguments; only numeric arguments.
406 (defmfun $rotation1 (phi th)
407 (let ((sinph (sin phi))
408 (cosph (cos phi))
409 (sinth (sin th))
410 (costh (cos th)))
411 `(($matrix simp)
412 ((mlist simp) ,(* cosph costh)
413 ,(* -1.0 cosph sinth)
414 ,sinph)
415 ((mlist simp) ,sinth ,costh 0.0)
416 ((mlist simp) ,(- (* sinph costh))
417 ,(* sinph sinth)
418 ,cosph))))
420 ;; pts is a vector of bts [x0,y0,z0,x1,y1,z1,...] and each tuple xi,yi,zi is rotated
421 #-abcl (defmfun $rotate_pts(pts rotation-matrix)
422 (or ($matrixp rotation-matrix) (merror (intl:gettext "rotate_pts: second argument must be a matrix.")))
423 (let* ((rot *rot*)
424 (l (length pts))
425 (x 0.0) (y 0.0) (z 0.0)
427 (declare (type flonum x y z))
428 (declare (type (cl:array flonum) rot))
429 ($copy_pts rotation-matrix *rot* 0)
431 (loop with j = 0
432 while (< j l)
434 (setq x (aref pts j))
435 (setq y (aref pts (+ j 1)))
436 (setq z (aref pts (+ j 2)))
437 (loop for i below 3 with a of-type flonum = 0.0
439 (setq a (* x (aref rot (+ (* 3 i) 0))))
440 (setq a (+ a (* y (aref rot (+ (* 3 i) 1)))))
441 (setq a (+ a (* z (aref rot (+ (* 3 i) 2)))))
442 (setf (aref pts (+ j i )) a))
443 (setf j (+ j 3)))))
445 (defmfun $rotate_list (x)
446 (cond ((and ($listp x) (not (mbagp (second x))))
447 ($list_matrix_entries (ncmul2 $rot x)))
448 ((mbagp x) (cons (car x) (mapcar '$rotate_list (cdr x))))))
450 (defmfun $get_range (pts k &aux (z 0.0) (max +most-negative-flonum+) (min +most-positive-flonum+))
451 (declare (type flonum z max min))
452 (declare (type (vector flonum) pts))
453 (loop for i from k below (length pts) by 3
454 do (setq z (aref pts i))
455 (cond ((< z min) (setq min z)))
456 (cond ((> z max) (setq max z))))
457 (list min max (- max min)))
459 (defmfun $polar_to_xy (pts &aux (r 0.0) (th 0.0))
460 (declare (type flonum r th))
461 (declare (type (cl:array t) pts))
462 (assert (typep pts '(vector t)))
463 (loop for i below (length pts) by 3
464 do (setq r (aref pts i))
465 (setq th (aref pts (+ i 1)))
466 (setf (aref pts i) (* r (cos th)))
467 (setf (aref pts (+ i 1)) (* r (sin th)))))
469 ;; Transformation from spherical coordinates to rectangular coordinates,
470 ;; to be used in plot3d. Example of its use:
471 ;; plot3d (expr, [th, 0, %pi], [ph, 0, 2*%pi], [transform_xy, spherical_to_xyz])
472 ;; where expr gives the value of r in terms of the inclination (th)
473 ;; and azimuth (ph).
475 (defmfun $spherical_to_xyz (pts &aux (r 0.0) (th 0.0) (ph 0.0))
476 (declare (type flonum r th ph))
477 (declare (type (cl:array t) pts))
478 (assert (typep pts '(vector t)))
479 (loop for i below (length pts) by 3
480 do (setq th (aref pts i))
481 (setq ph (aref pts (+ i 1)))
482 (setq r (aref pts (+ i 2)))
483 (setf (aref pts i) (* r (sin th) (cos ph)))
484 (setf (aref pts (+ i 1)) (* r (sin th) (sin ph)))
485 (setf (aref pts (+ i 2)) (* r (cos th)))))
488 ;; return a function suitable for the transform function in plot3d.
489 ;; FX, FY, and FZ are functions of three arguments.
490 (defmfun $make_transform (lvars fx fy fz)
491 (setq fx (coerce-float-fun fx lvars "make_transform"))
492 (setq fy (coerce-float-fun fy lvars "make_transform"))
493 (setq fz (coerce-float-fun fz lvars "make_transform"))
494 (let ((sym (gensym "transform")))
495 (setf (symbol-function sym)
496 #'(lambda (pts &aux (x1 0.0)(x2 0.0)(x3 0.0))
497 (declare (type flonum x1 x2 x3))
498 (declare (type (cl:array t) pts))
499 (loop for i below (length pts) by 3
501 (setq x1 (aref pts i))
502 (setq x2 (aref pts (+ i 1)))
503 (setq x3 (aref pts (+ i 2)))
504 (setf (aref pts i) (funcall fx x1 x2 x3))
505 (setf (aref pts (+ 1 i)) (funcall fy x1 x2 x3))
506 (setf (aref pts (+ 2 i)) (funcall fz x1 x2 x3)))))))
508 ;; Return value is a Lisp function which evaluates EXPR to a float.
509 ;; COERCE-FLOAT-FUN always returns a function and never returns a symbol,
510 ;; even if EXPR is a symbol.
512 ;; Following cases are recognized:
513 ;; EXPR is a symbol
514 ;; name of a Lisp function
515 ;; name of a Maxima function
516 ;; name of a DEFMSPEC function
517 ;; name of a Maxima macro
518 ;; a string which is the name of a Maxima operator (e.g., "!")
519 ;; name of a simplifying function
520 ;; EXPR is a Maxima lambda expression
521 ;; EXPR is a general Maxima expression
523 ;; %COERCE-FLOAT-FUN is the main internal routine for this.
524 ;; COERCE-FLOAT-FUN is the user interface for creating a function that
525 ;; returns floats. COERCE-BFLOAT-FUN is the same, except bfloats are
526 ;; returned.
527 (defun %coerce-float-fun (float-fun expr &rest rest &aux lvars fname)
528 (case (length rest)
529 (0 (setq lvars nil) (setq fname "coerce-float-fun"))
530 (1 (setq lvars (first rest)) (setq fname "coerce-float-fun"))
531 (2 (setq lvars (first rest)) (setq fname (second rest)))
532 (t (merror (intl:gettext "coerce-float-fun: two many arguments given."))))
533 (cond ((and (consp expr) (functionp expr))
534 (let ((args (if lvars (cdr lvars) (list (gensym)))))
535 (coerce-lisp-function-or-lisp-lambda args expr :float-fun float-fun)))
536 ;; expr is a string which names an operator
537 ;; (e.g. "!" "+" or a user-defined operator)
538 ((and (stringp expr) (getopr0 expr))
539 (let ((a (if lvars lvars `((mlist) ,(gensym)))))
540 (%coerce-float-fun float-fun `(($apply) ,(getopr0 expr) ,a) a fname)))
541 ((and (symbolp expr) (not (member expr lvars)) (not ($constantp expr)))
542 (cond
543 ((fboundp expr)
544 (let ((args (if lvars (cdr lvars) (list (gensym)))))
545 (coerce-lisp-function-or-lisp-lambda args expr :float-fun float-fun)))
546 ;; expr is name of a Maxima function defined by := or
547 ;; define
548 ((mget expr 'mexpr)
549 (let*
550 ((mexpr (mget expr 'mexpr))
551 (args (cdr (second mexpr))))
552 (coerce-maxima-function-or-maxima-lambda
553 args expr :float-fun float-fun)))
554 ((or
555 ;; expr is the name of a function defined by defmspec
556 (get expr 'mfexpr*)
557 ;; expr is the name of a Maxima macro defined by ::=
558 (mget expr 'mmacro)
559 ;; expr is the name of a simplifying function, and the
560 ;; simplification property is associated with the noun
561 ;; form
562 (get ($nounify expr) 'operators)
563 ;; expr is the name of a simplifying function, and the
564 ;; simplification property is associated with the verb
565 ;; form
566 (get ($verbify expr) 'operators))
567 (let ((a (if lvars lvars `((mlist) ,(gensym)))))
568 (%coerce-float-fun float-fun `(($apply) ,expr ,a) a fname)))
570 (merror (intl:gettext "~a: unknown function: ~M")
571 fname expr))))
572 ((and (consp expr) (eq (caar expr) 'lambda))
573 (let ((args (cdr (second expr))))
574 (coerce-maxima-function-or-maxima-lambda
575 args expr :float-fun float-fun)))
577 (let* ((vars (or lvars ($sort ($listofvars expr))))
578 (subscripted-vars ($sublist vars '((lambda) ((mlist) $x) ((mnot) (($atom) $x)))))
579 gensym-vars save-list-gensym subscripted-vars-save
580 subscripted-vars-mset subscripted-vars-restore)
582 ;; VARS and SUBSCRIPTED-VARS are Maxima lists. Other lists are
583 ;; Lisp lists.
584 (when (cdr subscripted-vars)
585 (setq gensym-vars (mapcar #'(lambda (ign) (declare (ignore ign)) (gensym))
586 (cdr subscripted-vars)))
587 (mapcar #'(lambda (a b) (setq vars (subst b a vars :test 'equal)))
588 (cdr subscripted-vars) gensym-vars)
590 ;; This stuff about saving and restoring array variables
591 ;; should go into MBINDING, and the lambda expression
592 ;; constructed below should call MBINDING. (At present
593 ;; MBINDING barfs on array variables.)
594 (setq save-list-gensym (gensym))
595 (setq subscripted-vars-save
596 (mapcar #'(lambda (a) `(push (meval ',a) ,save-list-gensym))
597 (cdr subscripted-vars)))
598 (setq subscripted-vars-mset
599 (mapcar #'(lambda (a b) `(mset ',a ,b))
600 (cdr subscripted-vars) gensym-vars))
601 (setq subscripted-vars-restore
602 (mapcar #'(lambda (a) `(mset ',a (pop ,save-list-gensym)))
603 (reverse (cdr subscripted-vars)))))
605 (coerce
606 `(lambda ,(cdr vars)
607 (declare (special ,@(cdr vars)))
609 ;; Nothing interpolated here when there are no subscripted
610 ;; variables.
611 ,@(if save-list-gensym `((declare (special ,save-list-gensym))))
613 ;; Nothing interpolated here when there are no subscripted
614 ;; variables.
615 ,@(if (cdr subscripted-vars)
616 `((progn (setq ,save-list-gensym nil)
617 ,@(append subscripted-vars-save subscripted-vars-mset))))
619 (let (($ratprint nil)
620 ;; We don't want to set $numer to T when coercing
621 ;; to a bigfloat. By doing so, things like
622 ;; log(400)^400 get converted to double-floats,
623 ;; which causes a double-float overflow. But the
624 ;; whole point of coercing to bfloat is to use
625 ;; bfloats, not doubles.
627 ;; Perhaps we don't even need to do this for
628 ;; double-floats? It would be nice to remove
629 ;; this. For backward compatibility, we bind
630 ;; numer to T if we're not trying to bfloat.
631 ($numer ,(not (eq float-fun '$bfloat)))
632 (*nounsflag* t))
633 ;; Catch any errors from evaluating the
634 ;; function. We're assuming that if an error
635 ;; is caught, the result is not a number. We
636 ;; also assume that for such errors, it's
637 ;; because the function is not defined there,
638 ;; not because of some other maxima error.
639 (let ((result
640 (errcatch (,float-fun (maybe-realpart (meval* ',expr))))))
642 ;; Nothing interpolated here when there are no
643 ;; subscripted variables.
644 ,@(if (cdr subscripted-vars) `((progn ,@subscripted-vars-restore)))
646 (if result
647 (car result)
648 t))))
649 'function)))))
650 ;; coerce-float-fun must be given an expression and one or two other optional
651 ;; arguments: a Maxima list of variables on which that expression depends
652 ;; and string that will identify the name of the responsible function
653 ;; when reporting errors.
654 (defun coerce-float-fun (expr &rest rest &aux lvars fname)
655 (case (length rest)
656 (0 (setq lvars nil) (setq fname "coerce-float-fun"))
658 (if (stringp (first rest))
659 (progn (setq lvars nil) (setq fname (first rest)))
660 (if ($listp (first rest))
661 (progn (setq lvars (first rest)) (setq fname "coerce-float-fun"))
662 (merror
663 (intl:gettext "coerce-float-fun: expecting a Maxima list, found: ~M")
664 (first rest)))))
666 (if ($listp (first rest))
667 (setq lvars (first rest))
668 (merror
669 (intl:gettext "coerce-float-fun: expecting a Maxima list, found: ~M")
670 (first rest)))
671 (if (stringp (second rest))
672 (setq fname (second rest))
673 (merror
674 (intl:gettext "coerce-float-fun: expecting a string, found: ~M")
675 (second rest))))
676 (t (merror (intl:gettext "coerce-float-fun: two many arguments given."))))
677 (%coerce-float-fun '$float expr lvars fname))
679 ;; coerce-bfloat-fun must be given an expression and one or two other optional
680 ;; arguments: a Maxima list of variables on which that expression depends
681 ;; and string that will identify the name of the responsible function
682 ;; when reporting errors.
683 (defun coerce-bfloat-fun (expr &rest rest &aux lvars fname)
684 (case (length rest)
685 (0 (setq lvars nil) (setq fname "coerce-bfloat-fun"))
687 (if (stringp (first rest))
688 (progn (setq lvars nil) (setq fname (first rest)))
689 (if ($listp (first rest))
690 (progn (setq lvars (first rest)) (setq fname "coerce-float-fun"))
691 (merror
692 (intl:gettext "coerce-bfloat-fun: expecting a Maxima list, found: ~M")
693 (first rest)))))
695 (if ($listp (first rest))
696 (setq lvars (first rest))
697 (merror
698 (intl:gettext "coerce-bfloat-fun: expecting a Maxima list, found: ~M")
699 (first rest)))
700 (if (stringp (second rest))
701 (setq fname (second rest))
702 (merror
703 (intl:gettext "coerce-bfloat-fun: expecting a string, found: ~M")
704 (second rest))))
705 (t (merror (intl:gettext "coerce-bfloat-fun: two many arguments given."))))
706 (%coerce-float-fun '$bfloat expr lvars fname))
708 (defun coerce-maxima-function-or-maxima-lambda
709 (args expr &key (float-fun '$float))
710 (let ((gensym-args (loop for x in args collect (gensym))))
711 (coerce
712 `(lambda ,gensym-args (declare (special ,@gensym-args))
713 ;; Just always try to convert the result with
714 ;; float-fun, which handles things like $%pi.
715 ;; See also BUG
716 ;; https://sourceforge.net/p/maxima/bugs/1795/
717 (let* (($ratprint nil)
718 ($numer t)
719 (*nounsflag* t)
720 (result
721 (errcatch
722 (,float-fun (maybe-realpart (mapply ',expr (list ,@gensym-args) t))))))
723 (if result
724 (car result)
725 t)))
726 'function)))
728 ;; Same as above, but call APPLY instead of MAPPLY.
730 (defun coerce-lisp-function-or-lisp-lambda
731 (args expr &key (float-fun '$float))
732 (let ((gensym-args (loop for x in args collect (gensym))))
733 (coerce
734 `(lambda ,gensym-args (declare (special ,@gensym-args))
735 (let* (($ratprint nil)
736 ($numer t)
737 (*nounsflag* t)
738 (result (maybe-realpart (apply ',expr (list ,@gensym-args)))))
739 ;; Always use float-fun. See comment for
740 ;; coerce-maxima-function-or-maxima-lambda above.
741 (,float-fun result)))
742 'function)))
744 (defmacro zval (points verts i) `(aref ,points (+ 2 (* 3 (aref ,verts ,i)))))
746 ;;sort the edges array so that drawing the edges will happen from the back towards
747 ;; the front. The if n==4 the edges array coming in looks like
748 ;; v1 v2 v3 v4 0 w1 w2 w3 w4 0 ...
749 ;; where vi,wi are indices pointint into the points array specifying a point
750 ;; in 3 space. After the sorting is done, the 0 is filled in with the vertex
751 ;; which is closer to us (ie highest z component after rotating towards the user)
752 ;; and this is then they are sorted in groups of 5.
753 (defun sort-ngons (points edges n &aux lis )
754 (declare (type (cl:array (flonum)) points)
755 (type (cl:array (mod #x80000000)) edges)
756 (fixnum n))
757 (let ((new (make-array (length edges) :element-type (array-element-type edges)))
758 (i 0)
759 (z 0.0)
760 (z1 0.0)
761 (n1 (- n 1))
762 (at 0)
763 (leng (length edges))
765 (declare (type (cl:array (mod #x80000000)) new)
766 (fixnum i leng n1 at )
768 (declare (type flonum z z1))
770 (setq lis
771 (loop for i0 below leng by (+ n 1)
773 (setq i i0)
774 (setq at 0)
775 (setq z (zval points edges i))
776 (setq i (+ i 1))
777 (loop for j below n1
778 do (if (> (setq z1 (zval points edges i)) z)
779 (setq z z1 at (aref edges i) ))
780 (setq i (+ i 1))
782 (setf (aref edges i) at)
783 collect (cons z i0)))
784 (setq lis (sort lis #'alphalessp :key #'car))
785 (setq i 0)
786 (loop for v in lis
788 (loop for j from (cdr v)
789 for k to n
790 do (setf (aref new i) (aref edges j))
791 (incf i))
793 (copy-array-portion edges new 0 0 (length edges))
796 (defun copy-array-portion (ar1 ar2 i1 i2 n1)
797 (declare (fixnum i1 i2 n1))
798 (loop while (>= (setq n1 (- n1 1)) 0)
799 do (setf (aref ar1 i1) (aref ar2 i2))
800 (setq i1 (+ i1 1))
801 (setq i2 (+ i2 1))))
803 (defmfun $concat_polygons (pl1 pl2 &aux tem new)
804 (setq new
805 (loop for v in pl1
806 for w in pl2
807 for l = (+ (length v) (length w))
808 do (setq tem (make-array l
809 :element-type (array-element-type v)
810 :fill-pointer l
813 collect tem))
814 (setq new (make-polygon (first new) (second new)) )
816 (copy-array-portion (polygon-pts pl1) (polygon-pts new)
817 0 0 (length (polygon-pts pl1)))
818 (copy-array-portion (polygon-pts pl2) (polygon-pts new)
819 (length (polygon-pts pl1))
820 0 (length (polygon-pts pl2)))
821 (copy-array-portion (polygon-edges pl1) (polygon-edges new)
822 0 0 (length (polygon-edges pl1)))
823 (loop for i from (length (polygon-edges pl1))
824 for j from 0 below (length (polygon-edges pl2))
825 with lpts1 = (length (polygon-pts pl1))
826 with ar2 = (polygon-edges pl2)
827 with arnew = (polygon-edges new)
828 do (setf (aref arnew i) (+ lpts1 (aref ar2 j)))))
830 (defmfun $copy_pts(lis vec start)
831 (declare (fixnum start))
832 (let ((tem vec))
833 (declare (type (cl:array flonum) tem))
834 (cond ((numberp lis)
835 (or (typep lis 'flonum) (setq lis (float lis)))
836 (setf (aref tem start) lis)
837 (1+ start))
838 ((typep lis 'cons)
839 ($copy_pts (cdr lis) vec ($copy_pts (car lis) vec start)))
840 ((symbolp lis) start)
841 (t (merror (intl:gettext "copy_pts: unrecognized first argument: ~M") lis)))))
843 ;; Implicit expressions of two variables, for instance, x and y,
844 ;; where expr is of the form f(x,y) = g(x,y).
845 ;; The result is a series of separated line segments.
847 (defun draw2d-implicit (expr options)
848 (let* ((xmin (first (getf options '$x)))
849 (ymin (first (getf options '$y)))
850 (xmax (second (getf options '$x)))
851 (ymax (second (getf options '$y)))
852 (gridx (or (first (getf options '$sample)) 47))
853 (gridy (or (second (getf options '$sample)) 47))
854 (eps (or (getf options '$plotepsilon) 1e-6))
855 (f (make-array `(,(1+ gridx) ,(1+ gridy))))
856 vx vy dx dy fun faux fmax fmin levels values result results)
857 (setq dx (/ (- xmax xmin) gridx) dy (/ (- ymax ymin) gridy))
858 (setq vx (getf options '$xvar) vy (getf options '$yvar))
859 (if (getf options '$contour)
860 (setq fun expr)
861 (setq fun (m- ($lhs expr) ($rhs expr))))
862 (setq fun (coerce-float-fun fun `((mlist) ,vx ,vy) "plot2d"))
863 ;; sets up array f with values of the function at corners of sample grid.
864 ;; finds maximum and minimum values in that array.
865 (dotimes (i (1+ gridx))
866 (dotimes (j (1+ gridy))
867 (setq faux (funcall fun (+ xmin (* i dx)) (+ ymin (* j dy))))
868 (setf (aref f i j) faux)
869 (when (and (numberp faux) (plusp i) (plusp j) (< i gridx) (< j gridy))
870 (if (numberp fmin)
871 (if (numberp fmax)
872 (progn
873 (when (< faux fmin) (setq fmin faux))
874 (when (> faux fmax) (setq fmax faux)))
875 (if (< faux fmin)
876 (setq fmax fmin fmin faux)
877 (setq fmax faux)))
878 (if (numberp fmax)
879 (if (> faux fmax)
880 (setq fmin fmax fmax faux)
881 (setq fmin faux))
882 (setq fmin faux))))))
883 ;; checks that the function has a minimum and a maximum
884 (when
886 (not (numberp fmin))
887 (not (numberp fmax)) (not (> fmax fmin)))
888 (merror (intl:gettext "plot2d: nothing to plot for ~M.~%") expr))
889 ;; sets up the levels for contour plots
890 (if (getf options '$contour)
891 (if (setq levels (getf options '$levels))
892 (unless (listp levels)
893 (setq levels (getlevels fmin fmax levels)))
894 (setq levels (getlevels fmin fmax 8)))
895 (setq levels (list 0.0)))
897 ;; Algorithm for implicit functions, by Jaime Villate. 2021
899 ;; The points at each rectangle in the sample grid are labeled as follows:
901 ;; ij+ ______ i+j+
902 ;; | |
903 ;; | | function fun has the following values at those points:
904 ;; | |
905 ;; ij |____| i+j fij, fi+j, fij+, fi+j+
907 (let (fij fi+j fij+ fi+j+ p1 p2 p3 p4 next)
908 (flet
909 ((interp+ (i j fi fi+ &aux x1 y1 x2 y2 (f1 fi) (f2 fi+) xp yp fp)
910 (if (minusp (* fi fi+))
911 (progn
912 (setq x1 (+ xmin (* dx i)))
913 (setq x2 (+ x1 dx))
914 (setq y1 (+ ymin (* dy j)))
915 (setq y2 (+ y1 dy))
916 (dotimes (n 2
917 (if (< (/ (+ (abs (- fi fp)) (abs (- fi+ fp)))
918 (abs (- fi fi+))) 1.5) (list xp yp) nil))
919 (setq xp (/ (+ x1 x2) 2.0))
920 (setq yp (/ (+ y1 y2) 2.0))
921 (setq fp (- (funcall fun xp yp) level))
922 (when (not (numberp fp)) (return nil))
923 (if (plusp (* f1 fp))
924 (setq x1 xp y1 yp f1 fp)
925 (setq x2 xp y2 yp f2 fp))
926 (setq xp (/ (- (* f1 x2) (* f2 x1)) (- f1 f2)))
927 (setq yp (/ (- (* f1 y2) (* f2 y1)) (- f1 f2)))
928 (setq fp (- (funcall fun xp yp) level))
929 (when (not (numberp fp)) (return nil))
930 (if (plusp (* f1 fp))
931 (setq x1 xp y1 yp f1 fp)
932 (setq x2 xp y2 yp f2 fp))))
933 nil))
934 (interp- (i j fi fi+ &aux x1 y1 x2 y2 (f1 fi) (f2 fi+) xp yp fp)
935 (if (minusp (* fi fi+))
936 (progn
937 (setq x1 (+ xmin (* dx i)))
938 (setq x2 (+ x1 dx))
939 (setq y1 (+ ymin (* dy j)))
940 (setq y2 (- y1 dy))
941 (dotimes (n 2
942 (if (< (/ (+ (abs (- fi fp)) (abs (- fi+ fp)))
943 (abs (- fi fi+))) 1.5) (list xp yp) nil))
944 (setq xp (/ (+ x1 x2) 2.0))
945 (setq yp (/ (+ y1 y2) 2.0))
946 (setq fp (- (funcall fun xp yp) level))
947 (when (not (numberp fp)) (return nil))
948 (if (plusp (* f1 fp))
949 (setq x1 xp y1 yp f1 fp)
950 (setq x2 xp y2 yp f2 fp))
951 (setq xp (/ (- (* f1 x2) (* f2 x1)) (- f1 f2)))
952 (setq yp (/ (- (* f1 y2) (* f2 y1)) (- f1 f2)))
953 (setq fp (- (funcall fun xp yp) level))
954 (when (not (numberp fp)) (return nil))
955 (if (plusp (* f1 fp))
956 (setq x1 xp y1 yp f1 fp)
957 (setq x2 xp y2 yp f2 fp))))
958 nil))
959 (interpx (i j fi fi+ &aux x1 x2 (f1 fi) (f2 fi+) xp yp fp)
960 (if (minusp (* fi fi+))
961 (progn
962 (setq x1 (+ xmin (* dx i)))
963 (setq x2 (+ x1 dx))
964 (setq yp (+ ymin (* dy j)))
965 (dotimes (n 2
966 (if (< (/ (+ (abs (- fi fp)) (abs (- fi+ fp)))
967 (abs (- fi fi+))) 1.5) (list xp yp) nil))
968 (setq xp (/ (+ x1 x2) 2.0))
969 (setq fp (- (funcall fun xp yp) level))
970 (when (not (numberp fp)) (return nil))
971 (if (plusp (* f1 fp))
972 (setq x1 xp f1 fp)
973 (setq x2 xp f2 fp))
974 (setq xp (/ (- (* f1 x2) (* f2 x1)) (- f1 f2)))
975 (setq fp (- (funcall fun xp yp) level))
976 (when (not (numberp fp)) (return nil))
977 (if (plusp (* f1 fp))
978 (setq x1 xp f1 fp)
979 (setq x2 xp f2 fp))))
980 nil))
981 (interpy (i j fj fj+ &aux y1 y2 (f1 fj) (f2 fj+) xp yp fp)
982 (if (minusp (* fj fj+))
983 (progn
984 (setq xp (+ xmin (* dx i)))
985 (setq y1 (+ ymin (* dy j)))
986 (setq y2 (+ y1 dy))
987 (dotimes (n 2
988 (if (< (/ (+ (abs (- fj fp)) (abs (- fj+ fp)))
989 (abs (- fj fj+))) 1.5) (list xp yp) nil))
990 (setq yp (/ (+ y1 y2) 2.0))
991 (setq fp (- (funcall fun xp yp) level))
992 (when (not (numberp fp)) (return nil))
993 (if (plusp (* f1 fp))
994 (setq y1 yp f1 fp)
995 (setq y2 yp f2 fp))
996 (setq yp (/ (- (* f1 y2) (* f2 y1)) (- f1 f2)))
997 (setq fp (- (funcall fun xp yp) level))
998 (when (not (numberp fp)) (return nil))
999 (if (plusp (* f1 fp))
1000 (setq y1 yp f1 fp)
1001 (setq y2 yp f2 fp))))
1002 nil))
1003 (coords (i j)
1004 (list (+ xmin (* i dx)) (+ ymin (* j dy))))
1005 (draw-line (p1 p2)
1006 (push (first p1) result)
1007 (push (second p1) result)
1008 (push (first p2) result)
1009 (push (second p2) result)
1010 (push 'moveto result)
1011 (push 'moveto result))
1012 (draw-lines (p1 p2 p3)
1013 (push (first p1) result)
1014 (push (second p1) result)
1015 (push (first p2) result)
1016 (push (second p2) result)
1017 (push (first p3) result)
1018 (push (second p3) result)
1019 (push 'moveto result)
1020 (push 'moveto result)))
1021 (dolist (level (reverse levels))
1022 (dotimes (i gridx)
1023 (dotimes (j gridy)
1024 (if (numberp (aref f i j))
1025 (setq fij (- (aref f i j) level))
1026 (setq fij (aref f i j)))
1027 (if (numberp (aref f i (1+ j)))
1028 (setq fij+ (- (aref f i (1+ j)) level))
1029 (setq fij+ (aref f i (1+ j))))
1030 (if (numberp (aref f (1+ i) j))
1031 (setq fi+j (- (aref f (1+ i) j) level))
1032 (setq fi+j (aref f (1+ i) j)))
1033 (if (numberp (aref f (1+ i) (1+ j)))
1034 (setq fi+j+ (- (aref f (1+ i) (1+ j)) level))
1035 (setq fi+j+ (aref f (1+ i) (1+ j))))
1036 (setq next t)
1037 ;; 1. undefined at ij
1038 (when (not (numberp fij))
1039 (setq next nil)
1040 ;; if undefined also at i+j or ij+, continue to next rectangle
1041 (when (and (numberp fi+j) (numberp fij+))
1042 (if (< (abs fi+j) eps)
1043 (if (< (abs fij+) eps)
1044 ;; real and 0 at i+j and ij+
1045 (draw-line (coords (1+ i) j) (coords i (1+ j)))
1046 (when
1047 (and
1048 (numberp fi+j+)
1049 (setq p2 (interpx i (1+ j) fij+ fi+j+)))
1050 ;; real at i+j, ij+ and i+j+, 0 at i+j and segment
1051 ;; ij+ i+j+
1052 (draw-line (coords (1+ i) j) p2)))
1053 (when (numberp fi+j+)
1054 (if (< (abs fij+) eps)
1055 (when (setq p2 (interpy (1+ i) j fi+j fi+j+))
1056 ;; real at i+j, and i+j+, 0 at ij+ and segment
1057 ;; i+j i+j+
1058 (draw-line (coords i (1+ j)) p2))
1059 (when
1060 (and
1061 (setq p1 (interpx i (1+ j) fij+ fi+j+))
1062 (setq p2 (interpy (1+ i) j fi+j fi+j+)))
1063 ;; real at i+j, ij+ and i+j+, 0 at segments
1064 ;; ij+ i+j+ and i+j i+j+
1065 (draw-line p1 p2)))))))
1066 ;; 2. real at ij and undefined at i+j
1067 (when (and next (not (numberp fi+j)))
1068 (setq next nil)
1069 ;; if undefined at ij+, continue to next rectangle
1070 (when (numberp fij+)
1071 (if (< (abs fij) eps)
1072 (if (< (abs fij+) eps)
1073 ;; zero at ij and ij+
1074 (draw-line (coords i j) (coords i (1+ j)))
1075 (when
1076 (and
1077 (numberp fi+j+)
1078 (setq p2 (interpx i (1+ j) fij+ fi+j+)))
1079 ;; real at ij+ and i+j+, 0 at ij and segment ij+ i+j+
1080 (draw-line (coords i j) p2)))
1081 (when
1082 (and
1083 (numberp fi+j+)
1084 (setq p1 (interpy i j fij fij+))
1085 (setq p2 (interpx i (1+ j) fij+ fi+j+)))
1086 ;; real at ij, ij+ and i+j+, 0 at segments ij ij+
1087 ;; and ij+ i+j+
1088 (draw-line p1 p2)))))
1089 ;; 3. real at fi+j and 0 at ij
1090 (when (and next (< (abs fij) eps))
1091 (setq next nil)
1092 (if (numberp fij+)
1093 (if (< (abs fij+) eps)
1094 ;; real at i+j, 0 at ij and ij+
1095 (draw-line (coords i j) (coords i (1+ j)))
1096 (when (setq p1 (interp- i (1+ j) fij+ fi+j))
1097 (if (numberp fi+j+)
1098 (if (< (abs fi+j+) eps)
1099 ;; real at i+j and ij, 0 at ij, i+j+ and
1100 ;; diagonal ij+ i+j
1101 (draw-lines (coords i j) p1
1102 (coords (1+ i) (1+ j)))
1103 (progn
1104 ;; real at i+j, ij+ and i+j+, 0 at ij,
1105 ;; diagonal ij+ i+j and segment ij+ i+j+
1106 (when (setq p2 (interpx i (1+ j) fij+ fi+j+))
1107 (draw-lines (coords i j) p1 p2))
1108 ;; real at i+j, ij+ and i+j+, 0 at ij,
1109 ;; diagonal ij+ i+j and segment i+j i+j+
1110 (when (setq p2 (interpy (1+ i) j fi+j fi+j+))
1111 (draw-lines (coords i j) p1 p2)))))))
1112 (if (numberp fi+j+)
1113 (if (< (abs fi+j) eps)
1114 ;; undefined at ij+, real at fi+j+, 0 at ij and i+j
1115 (draw-line (coords i j) (coords (1+ i) j))
1116 (when (setq p2 (interpy (1+ i) j fi+j fi+j+))
1117 ;; undefined at ij+, real at fi+j and fi+j+, 0 at
1118 ;; ij and segment i+j i+j+
1119 (draw-line (coords i j) p2)))
1120 (when (< (abs fi+j) eps)
1121 ;; undefined at ij+ and i+j+, 0 at ij and i+j
1122 (draw-line (coords i j) (coords (1+ i) j))))))
1123 ;; 4. real at ij and 0 at i+j
1124 (when (and next (< (abs fi+j) eps))
1125 (setq next nil)
1126 (if (numberp fij+)
1127 (if (numberp fi+j+)
1128 ;; if 0 at i+j but undefined at ij+ or there's no zero
1129 ;; in diagonal ij i+j+, continue to next rectangle
1130 (when (setq p1 (interp+ i j fij fi+j+))
1131 (if (< (abs fij+) eps)
1132 ;; 0 at i+j, ij+ and diagonal ij i+j+
1133 (draw-lines (coords (1+ i) j) p1 (coords i (1+ j)))
1134 (progn
1135 (when (setq p2 (interpy i j fij fij+))
1136 ;; 0 at i+j, diagonal ij i+j+ and segment
1137 ;; ij ij+
1138 (draw-lines (coords (1+ i) j) p1 p2))
1139 (when (setq p2 (interpx i (1+ j) fij+ fi+j+))
1140 ;; 0 at i+j, diagonal ij i+j+ and segment
1141 ;; ij+ i+j+
1142 (draw-lines (coords (1+ i) j) p1 p2)))))
1143 (when (setq p2 (interpy i j fij fij+))
1144 ;; undefined at i+j+, 0 at i+j and segment ij ij+
1145 (draw-line (coords (1+ i) j) p2)))))
1146 ;; 5. real at ij and i+j but undefined at ij+
1147 (when (and next (not (numberp fij+)))
1148 (setq next nil)
1149 (when
1150 (and
1151 (numberp fi+j+)
1152 (setq p1 (interpx i j fij fi+j))
1153 (setq p2 (interpy (1+ i) j fi+j fi+j+)))
1154 ;; 0 at segments ij i+j and i+j i+j+
1155 (draw-line p1 p2)))
1156 ;; 6. real at ij, i+j and ij+, but undefined at i+j+
1157 (when (and next (not (numberp fi+j+)))
1158 (setq next nil)
1159 (when
1160 (and
1161 (setq p1 (interpy i j fij fij+))
1162 (setq p2 (interpx i j fij fi+j)))
1163 ;; 0 at segments ij ij+ and ij i+j
1164 (draw-line p1 p2)))
1165 ;; 7. real at the four corners and 0 at ij+
1166 (when (and next (< (abs fij+) eps))
1167 (setq next nil)
1168 (when (setq p1 (interp+ i j fij fi+j+))
1169 (when (setq p2 (interpx i j fij fi+j))
1170 ;; 0 at diagonal ij i+j+ and segment ij i+j
1171 (draw-lines p2 p1 (coords i (1+ j))))
1172 (when (setq p2 (interpy (1+ i) j fi+j fi+j+))
1173 ;; 0 at diagonal ij i+j+ and segment i+j i+j+
1174 (draw-lines p2 p1 (coords i (1+ j))))))
1175 ;; 8. real at the four corners and 0 at i+j+
1176 (when (and next (< (abs fi+j+) eps))
1177 (setq next nil)
1178 (when (setq p1 (interp- i (1+ j) fij+ fi+j))
1179 (when (setq p2 (interpx i j fij fi+j))
1180 ;; 0 at diagonal ij+ i+j and segment ij i+j
1181 (draw-lines p2 p1 (coords (1+ i) (1+ j))))
1182 (when (setq p2 (interpy i j fij fij+))
1183 ;; 0 at diagonal ij+ i+j and segment ij ij+
1184 (draw-lines p2 p1 (coords (1+ i) (1+ j))))))
1185 ;; 9. real at the four corners and 0 at segment ij i+j
1186 (when (and next (setq p1 (interpx i j fij fi+j)))
1187 (setq next nil)
1188 (if (setq p2 (interpy i j fij fij+))
1189 (if (setq p3 (interpx i (1+ j) fij+ fi+j+))
1190 (when (setq p4 (interpy (1+ i) j fi+j fi+j+))
1191 ;; 0 at the four sides
1192 (draw-line p1 p3)
1193 (draw-line p2 p4))
1194 (when (setq p3 (interp+ i j fij fi+j+))
1195 ;; 0 at segments ij i+j, ij ij+ and diagonal ij i+j+
1196 (draw-lines p1 p3 p2)))
1197 (if (setq p4 (interpy (1+ i) j fi+j fi+j+))
1198 (when (setq p2 (interp- i (1+ j) fij+ fi+j))
1199 ;; 0 at segments ij i+j, i+j i+j+ and diagonal ij+ i+j
1200 (draw-lines p1 p2 p4))
1201 (when
1202 (and
1203 (setq p3 (interpx i (1+ j) fij+ fi+j+))
1204 (setq p2 (interp+ i j fij fi+j+)))
1205 ;; 0 at segments ij i+j, ij+ i+j+ and diagonal ij i+j+
1206 (draw-lines p1 p2 p3)))))
1207 ;; 10. real at the four corners, without zero in segment ij i+j
1208 (when next
1209 (if (setq p2 (interpy i j fij fij+))
1210 (if (setq p3 (interpx i (1+ j) fij+ fi+j+))
1211 (when (setq p4 (interp- i (1+ j) fij+ fi+j))
1212 ;; 0 at segments ij ij+ and ij+ i+j+ and diagonal
1213 ;; ij+ i+j
1214 (draw-lines p2 p4 p3))
1215 (when
1216 (and
1217 (setq p4 (interpy (1+ i) j fi+j fi+j+))
1218 (setq p3 (interp+ i j fij fi+j+)))
1219 ;; 0 at segments ij ij+ and i+j i+j+ and diagonal
1220 ;; ij i+j+
1221 (draw-lines p2 p3 p4)))
1222 (when
1223 (and
1224 (setq p3 (interpx i (1+ j) fij+ fi+j+))
1225 (setq p4 (interpy (1+ i) j fi+j fi+j+))
1226 (setq p1 (interp+ i j fij fi+j+)))
1227 ;; 0 at segments ij+ i+j+ and i+j i+j+ and diagonal
1228 ;; ij i+j+
1229 (draw-lines p4 p1 p3))))))
1230 (when (and (getf options '$contour) result)
1231 (push (cons '(mlist) (reverse result)) results)
1232 (push level values)
1233 (setq result nil)))))
1234 ;; When called for a single implicit expression, returns a Maxima list
1235 ;; of points. When called for contours of an expression, returns a
1236 ;; Maxima list whose first element is another Maxima list with the values
1237 ;; of the contours, followed by Maxima lists of points for each contour.
1238 (if (getf options '$contour)
1239 (cons '(mlist) (cons (cons '(mlist) values) results))
1240 (cons '(mlist) (reverse result)))))
1242 ;; parametric ; [parametric,xfun,yfun,[t,tlow,thigh],[nticks ..]]
1243 ;; the rest of the parametric list after the list will add to the plot options
1245 (defun draw2d-parametric-adaptive (param options &aux range)
1246 (or (= ($length param) 4)
1247 (merror (intl:gettext "plot2d: parametric plots must include two expressions and an interval")))
1248 (setq range (nth 4 param))
1249 (or (and ($listp range) (symbolp (second range)) (eql ($length range) 3))
1250 (merror (intl:gettext "plot2d: wrong interval for parametric plot: ~M")
1251 range))
1252 (setq range (check-range range))
1253 (let* ((nticks (getf options '$nticks))
1254 (trange (cddr range))
1255 (tvar (second range))
1256 (xrange (or (getf options '$x) (getf options '$xbounds)))
1257 (yrange (or (getf options '$y) (getf options '$ybounds)))
1258 (tmin (coerce-float (first trange)))
1259 (tmax (coerce-float (second trange)))
1260 (xmin (coerce-float (first xrange)))
1261 (xmax (coerce-float (second xrange)))
1262 (ymin (coerce-float (first yrange)))
1263 (ymax (coerce-float (second yrange)))
1264 f1 f2)
1265 (declare (type flonum ymin ymax xmin xmax tmin tmax))
1266 (setq f1 (coerce-float-fun (third param) `((mlist), tvar) "plot2d"))
1267 (setq f2 (coerce-float-fun (fourth param) `((mlist), tvar) "plot2d"))
1269 (let ((n-clipped 0) (n-non-numeric 0)
1270 (t-step (/ (- tmax tmin) (coerce-float nticks) 2))
1271 t-samples x-samples y-samples result)
1272 ;; Divide the range into 2*NTICKS regions that we then
1273 ;; adaptively plot over.
1274 (dotimes (k (1+ (* 2 nticks)))
1275 (let ((tpar (+ tmin (* k t-step))))
1276 (push tpar t-samples)
1277 (push (funcall f1 tpar) x-samples)
1278 (push (funcall f2 tpar) y-samples)))
1279 (setf t-samples (nreverse t-samples))
1280 (setf x-samples (nreverse x-samples))
1281 (setf y-samples (nreverse y-samples))
1283 ;; Adaptively plot over each region
1284 (do ((t-start t-samples (cddr t-start))
1285 (t-mid (cdr t-samples) (cddr t-mid))
1286 (t-end (cddr t-samples) (cddr t-end))
1287 (x-start x-samples (cddr x-start))
1288 (x-mid (cdr x-samples) (cddr x-mid))
1289 (x-end (cddr x-samples) (cddr x-end))
1290 (y-start y-samples (cddr y-start))
1291 (y-mid (cdr y-samples) (cddr y-mid))
1292 (y-end (cddr y-samples) (cddr y-end)))
1293 ((null t-end))
1294 (setf result
1295 (if result
1296 (append result
1297 (cddr (adaptive-parametric-plot
1298 f1 f2
1299 (car t-start) (car t-mid) (car t-end)
1300 (car x-start) (car x-mid) (car x-end)
1301 (car y-start) (car y-mid) (car y-end)
1302 (getf options '$adapt_depth)
1303 1e-5)))
1304 (adaptive-parametric-plot
1305 f1 f2
1306 (car t-start) (car t-mid) (car t-end)
1307 (car x-start) (car x-mid) (car x-end)
1308 (car y-start) (car y-mid) (car y-end)
1309 (getf options '$adapt_depth)
1310 1e-5))))
1311 ;; Fix up out-of-range values and clobber non-numeric values.
1312 (do ((x result (cddr x))
1313 (y (cdr result) (cddr y)))
1314 ((null y))
1315 (if (and (numberp (car x)) (numberp (car y)))
1316 ;; Let clipping to the graphic program. See the comment in DRAW2D.
1317 (unless (and (<= ymin (car y) ymax)
1318 (<= xmin (car x) xmax))
1319 (incf n-clipped))
1320 (progn
1321 (incf n-non-numeric)
1322 (setf (car x) 'moveto)
1323 (setf (car y) 'moveto))))
1324 ;; Filter out any MOVETO's which do not precede a number.
1325 ;; Code elsewhere in this file expects MOVETO's to
1326 ;; come in pairs, so leave two MOVETO's before a number.
1327 (let ((n (length result)))
1328 (dotimes (i n)
1329 (when
1330 (and
1331 (evenp i)
1332 (eq (nth i result) 'moveto)
1333 (eq (nth (1+ i) result) 'moveto)
1334 (or
1335 (eq i (- n 2))
1336 (eq (nth (+ i 2) result) 'moveto)))
1337 (setf (nth i result) nil)
1338 (setf (nth (1+ i) result) nil))))
1340 (let ((result-sans-nil (delete nil result)))
1341 (if (null result-sans-nil)
1342 (cond
1343 ((= n-non-numeric 0)
1344 (mtell (intl:gettext "plot2d: all values will be clipped.~%")))
1345 ((= n-clipped 0)
1346 (mtell (intl:gettext
1347 "plot2d: expression evaluates to non-numeric value everywhere in plotting range.~%")))
1349 (mtell (intl:gettext
1350 "plot2d: all values are non-numeric, or clipped.~%"))))
1351 (progn
1352 (if (> n-non-numeric 0)
1353 (mtell (intl:gettext
1354 "plot2d: expression evaluates to non-numeric value somewhere in plotting range.~%")))
1355 (if (> n-clipped 0)
1356 (mtell (intl:gettext "plot2d: some values will be clipped.~%")))))
1357 (cons '(mlist) result-sans-nil)))))
1359 ;; draw2d-discrete. Accepts [discrete,[x1,x2,...],[y1,y2,...]]
1360 ;; or [discrete,[[x1,y1]...] and returns [x1,y1,...] or nil, if none of the
1361 ;; points have real values.
1362 ;; Currently there are no plot options relevant to draw2d-discrete.
1363 (defun draw2d-discrete (f)
1364 (let ((x (third f)) (y (fourth f)) (n-clipped 0) data gaps)
1365 (cond
1366 (($listp x) ; x is a list
1367 (cond
1368 (($listp (cadr x)) ; x1 is a list
1369 (cond
1370 ((= (length (cadr x)) 3) ; x1 is a 2D point
1371 (setq data (parse-points-xy x)))
1372 (t ; x1 is not a 2D point
1373 (merror (intl:gettext "draw2d-discrete: Expecting a point with 2 coordinates; found ~M~%") (cadr x)))))
1374 (t ; x1 is not a list
1375 (cond
1376 (($listp y) ; y is a list
1377 (cond
1378 ((symbolp (coerce-float (cadr y))); y is an option
1379 (setq data (parse-points-y x)))
1380 (t ; y is not an option
1381 (cond
1382 (($listp (cadr y)) ; y1 is a list
1383 (merror (intl:gettext "draw2d-discrete: Expecting a y coordinate; found ~M~%") (cadr y)))
1384 (t ; y1 not a list
1385 (cond
1386 ((= (length x) (length y)) ; case [x][y]
1387 (setq data (parse-points-x-y x y)))
1388 (t ; wrong
1389 (merror (intl:gettext "draw2d-discrete: The number of x and y coordinates do not match.~%")))))))))
1390 (t ; y is not a list
1391 (setq data (parse-points-y x)))))))
1392 (t ; x is not a list
1393 (merror (intl:gettext "draw2d-discrete: Expecting a list of x coordinates or points; found ~M~%") x)))
1395 ;; checks for non-real values
1396 (cond
1397 ((some #'realp data)
1398 (setq gaps (count-if #'(lambda (x) (eq x 'moveto)) data))
1399 (when (= gaps 2)
1400 ;; one point has non-real value
1401 (mtell (intl:gettext "Warning: excluding 1 point with non-numerical value.~%")))
1402 (when (> gaps 2)
1403 ;; some points have non-real values
1404 (mtell (intl:gettext "Warning: excluding ~M points with non-numerical values.~%") (/ gaps 2))))
1406 ;; none of the points have real values
1407 (mtell (intl:gettext "Warning: none of the points have numerical values.~%"))
1408 (setq data nil)))
1409 data))
1411 ;; Two lists [x1...xn] and [y1...yn] are joined as
1412 ;; [x1 y1...xn yn], converting all expressions to real numbers.
1413 ;; If either xi or yi are not real, both are replaced by 'moveto
1414 (defun parse-points-x-y (x y)
1415 (do ((a (rest x) (cdr a))
1416 (b (rest y) (cdr b))
1417 c af bf)
1418 ((null b) (cons '(mlist) (reverse c)))
1419 (setq af (coerce-float (car a)))
1420 (setq bf (coerce-float (car b)))
1421 (cond
1422 ((or (not (realp af)) (not (realp bf)))
1423 (setq c (cons 'moveto (cons 'moveto c))))
1425 (setq c (cons bf (cons af c)))))))
1427 ;; One list [y1...yn] becomes the list [1 y1...n yn],
1428 ;; converting all expressions to real numbers.
1429 ;; If yi is not real, both i and yi are replaced by 'moveto
1430 (defun parse-points-y (y)
1431 (do ((a 1 (1+ a))
1432 (b (rest y) (cdr b))
1433 c bf)
1434 ((null b) (cons '(mlist) (reverse c)))
1435 (setq bf (coerce-float (car b)))
1436 (cond
1437 ((not (realp bf))
1438 (setq c (cons 'moveto (cons 'moveto c))))
1440 (setq c (cons bf (cons a c)))))))
1442 ;; List [[x1,y1]...[xn,yn]] is transformed into
1443 ;; [x1 y1...xn yn], converting all expressions to real numbers.
1444 ;; If either xi or yi are not real, both are replaced by 'moveto
1445 (defun parse-points-xy (xy)
1446 (do ((ab (rest xy) (cdr ab))
1447 c af bf)
1448 ((null ab) (cons '(mlist) (reverse c)))
1449 (setq af (coerce-float (cadar ab)))
1450 (setq bf (coerce-float (caddar ab)))
1451 (cond
1452 ((or (not (realp af)) (not (realp bf)))
1453 (setq c (cons 'moveto (cons 'moveto c))))
1455 (setq c (cons bf (cons af c)))))))
1457 ;;; Adaptive plotting, based on the adaptive plotting code from
1458 ;;; YACAS. See http://yacas.sourceforge.net/Algo.html#c3s1 for a
1459 ;;; description of the algorithm. More precise details can be found
1460 ;;; in the file yacas/scripts/plots.rep/plot2d.ys.
1463 ;; Determine if we have a slow oscillation of the function.
1464 ;; Basically, for each 3 consecutive function values, we check to see
1465 ;; if the function is monotonic or not. There are 3 such sets, and
1466 ;; the function is considered slowly oscillating if at most 2 of them
1467 ;; are not monotonic.
1468 (defun slow-oscillation-p (f0 f1 f2 f3 f4)
1469 (flet ((sign-change (x y z)
1470 (cond ((not (and (numberp x) (numberp y) (numberp z)))
1471 ;; Something is not a number. Assume the
1472 ;; oscillation is not slow.
1474 ((or (and (> y x) (> y z))
1475 (and (< y x) (< y z)))
1478 0))))
1479 (<= (+ (sign-change f0 f1 f2)
1480 (sign-change f1 f2 f3)
1481 (sign-change f2 f3 f4))
1482 2)))
1484 ;; Determine if the function values are smooth enough. This means
1485 ;; that integrals of the functions on the left part and the right part
1486 ;; of the range are approximately the same.
1489 (defun smooth-enough-p (f-a f-a1 f-b f-b1 f-c eps)
1490 (cond ((every #'numberp (list f-a f-a1 f-b f-b1 f-c))
1491 (let ((quad (/ (+ f-a
1492 (* -5 f-a1)
1493 (* 9 f-b)
1494 (* -7 f-b1)
1495 (* 2 f-c))
1496 24))
1497 (quad-b (/ (+ (* 5 f-b)
1498 (* 8 f-b1)
1499 (- f-c))
1500 12)))
1501 ;; According to the Yacas source code, quad is the Simpson
1502 ;; quadrature for the (fb,fb1) subinterval (using points b,b1,c),
1503 ;; subtracted from the 4-point Newton-Cotes quadrature for the
1504 ;; (fb,fb1) subinterval (using points a, a1, b, b1.
1506 ;; quad-b is the Simpson quadrature for the (fb,f1) subinterval.
1508 ;; This used to test for diff <= 0. But in some
1509 ;; situations, like plot2d(0.99,[x,0,5]), roundoff prevents
1510 ;; this from happening. So we do diff < delta instead, for
1511 ;; some value of delta.
1513 ;; XXX: What is the right value for delta? Does this break
1514 ;; other things? Simple tests thus far show that
1515 ;; 100*flonum-epsilon is ok.
1516 (let ((diff (- (abs quad)
1517 (* eps (- quad-b (min f-a f-a1 f-b f-b1 f-c)))))
1518 (delta (* 150 +flonum-epsilon+)))
1519 (<= diff delta))))
1521 ;; Something is not a number, so assume it's not smooth enough.
1522 nil)))
1524 (defun adaptive-plot (fcn a b c f-a f-b f-c depth eps)
1525 ;; Step 1: Split the interval [a, c] into 5 points
1526 (let* ((a1 (/ (+ a b) 2))
1527 (b1 (/ (+ b c) 2))
1528 (f-a1 (funcall fcn a1))
1529 (f-b1 (funcall fcn b1))
1531 (cond ((or (not (plusp depth))
1532 (and (slow-oscillation-p f-a f-a1 f-b f-b1 f-c)
1533 (smooth-enough-p f-a f-a1 f-b f-b1 f-c eps)))
1534 ;; Everything is nice and smooth so we're done. Don't
1535 ;; refine anymore.
1536 (list a f-a
1537 a1 f-a1
1538 b f-b
1539 b1 f-b1
1540 c f-c))
1541 ;; We are not plotting the real part of the function and the
1542 ;; function is undefined at all points - assume it has complex value
1543 ;; on [a,b]. Maybe we should refine it a couple of times just to make sure?
1544 ((and (null *plot-realpart*)
1545 (null f-a) (null f-a1) (null f-b) (null f-b1) (null f-c))
1546 (list a f-a
1547 a1 f-a1
1548 b f-b
1549 b1 f-b1
1550 c f-c))
1552 ;; Need to refine. Split the interval in half, and try to plot each half.
1553 (let ((left (adaptive-plot fcn a a1 b f-a f-a1 f-b (1- depth) (* 2 eps)))
1554 (right (adaptive-plot fcn b b1 c f-b f-b1 f-c (1- depth) (* 2 eps))))
1555 (append left (cddr right)))))))
1557 (defun adaptive-parametric-plot (x-fcn y-fcn a b c x-a x-b x-c y-a y-b y-c depth eps)
1558 ;; Step 1: Split the interval [a, c] into 5 points
1559 (let* ((a1 (/ (+ a b) 2))
1560 (b1 (/ (+ b c) 2))
1561 (x-a1 (funcall x-fcn a1))
1562 (x-b1 (funcall x-fcn b1))
1563 (y-a1 (funcall y-fcn a1))
1564 (y-b1 (funcall y-fcn b1)))
1565 (cond ((or (not (plusp depth))
1566 ;; Should we have a different algorithm to determine
1567 ;; slow oscillation and smooth-enough for parametric
1568 ;; plots?
1569 (and (slow-oscillation-p y-a y-a1 y-b y-b1 y-c)
1570 (slow-oscillation-p x-a x-a1 x-b x-b1 x-c)
1571 (smooth-enough-p y-a y-a1 y-b y-b1 y-c eps)
1572 (smooth-enough-p x-a x-a1 x-b x-b1 x-c eps)))
1573 ;; Everything is nice and smooth so we're done. Don't
1574 ;; refine anymore.
1575 (list x-a y-a
1576 x-a1 y-a1
1577 x-b y-b
1578 x-b1 y-b1
1579 x-c y-c))
1580 ;; We are not plotting the real part of the function and the
1581 ;; function is undefined at all points - assume it has complex value
1582 ;; on [a,b]. Maybe we should refine it a couple of times just to make sure?
1583 ((and (null *plot-realpart*)
1584 (null y-a) (null y-a1) (null y-b) (null y-b1) (null y-c)
1585 (null x-a) (null x-a1) (null x-b) (null x-b1) (null x-c))
1586 (list x-a y-a
1587 x-a1 y-a1
1588 x-b y-b
1589 x-b1 y-b1
1590 x-c y-c))
1592 ;; Need to refine. Split the interval in half, and try to plot each half.
1593 (let ((left (adaptive-parametric-plot x-fcn y-fcn
1594 a a1 b
1595 x-a x-a1 x-b
1596 y-a y-a1 y-b
1597 (1- depth) (* 2 eps)))
1598 (right (adaptive-parametric-plot x-fcn y-fcn
1599 b b1 c
1600 x-b x-b1 x-c
1601 y-b y-b1 y-c
1602 (1- depth) (* 2 eps))))
1603 ;; (cddr right) to skip over the point that is duplicated
1604 ;; between the right end-point of the left region and the
1605 ;; left end-point of the right
1606 (append left (cddr right)))))))
1608 (defun draw2d (fcn range plot-options)
1609 (if (and ($listp fcn) (equal '$parametric (cadr fcn)))
1610 (return-from draw2d
1611 (draw2d-parametric-adaptive fcn plot-options)))
1612 (if (and ($listp fcn) (equal '$discrete (cadr fcn)))
1613 (return-from draw2d (draw2d-discrete fcn)))
1614 (when (and ($listp fcn) (equal '$contour (cadr fcn)))
1615 (setf (getf plot-options '$contour) t)
1616 (return-from draw2d (draw2d-implicit (caddr fcn) plot-options)))
1617 (when (and (listp fcn) (eq 'mequal (caar fcn)))
1618 (setf (getf plot-options '$contour) nil)
1619 (return-from draw2d (draw2d-implicit fcn plot-options)))
1620 (let* ((nticks (getf plot-options '$nticks))
1621 (yrange (getf plot-options '$ybounds))
1622 (depth (getf plot-options '$adapt_depth)))
1624 (setq fcn (coerce-float-fun fcn `((mlist), (second range)) "plot2d"))
1626 (let* ((x-start (coerce-float (third range)))
1627 (xend (coerce-float (fourth range)))
1628 (x-step (/ (- xend x-start) (coerce-float nticks) 2))
1629 (ymin (coerce-float (first yrange)))
1630 (ymax (coerce-float (second yrange)))
1631 (n-clipped 0) (n-non-numeric 0)
1632 ;; What is a good EPS value for adaptive plotting?
1633 ;(eps 1e-5)
1634 x-samples y-samples result
1636 (declare (type flonum ymin ymax))
1637 ;; Divide the region into NTICKS regions. Each region has a
1638 ;; start, mid and endpoint. Then adaptively plot over each of
1639 ;; these regions. So it's probably a good idea not to make
1640 ;; NTICKS too big. Since adaptive plotting splits the sections
1641 ;; in half, it's also probably not a good idea to have NTICKS be
1642 ;; a power of two.
1643 (when (getf plot-options '$logx)
1644 (setf x-start (log x-start))
1645 (setf xend (log xend))
1646 (setf x-step (/ (- xend x-start) (coerce-float nticks) 2)))
1648 (flet ((fun (x)
1649 (let ((y (if (getf plot-options '$logx)
1650 (funcall fcn (exp x))
1651 (funcall fcn x))))
1652 (if (and (getf plot-options '$logy)
1653 (numberp y))
1654 (if (> y 0) (log y) 'und)
1655 y))))
1657 (dotimes (k (1+ (* 2 nticks)))
1658 (let ((x (+ x-start (* k x-step))))
1659 (push x x-samples)
1660 (push (fun x) y-samples)))
1661 (setf x-samples (nreverse x-samples))
1662 (setf y-samples (nreverse y-samples))
1664 ;; For each region, adaptively plot it.
1665 (do ((x-start x-samples (cddr x-start))
1666 (x-mid (cdr x-samples) (cddr x-mid))
1667 (x-end (cddr x-samples) (cddr x-end))
1668 (y-start y-samples (cddr y-start))
1669 (y-mid (cdr y-samples) (cddr y-mid))
1670 (y-end (cddr y-samples) (cddr y-end)))
1671 ((null x-end))
1672 ;; The region is x-start to x-end, with mid-point x-mid.
1674 ;; The cddr is to remove the one extra sample (x and y value)
1675 ;; that adaptive plot returns. But on the first iteration,
1676 ;; result is empty, so we don't want the cddr because we want
1677 ;; all the samples returned from adaptive-plot. On subsequent
1678 ;; iterations, it's a duplicate of the last point of the
1679 ;; previous interval.
1680 (setf result
1681 (if result
1682 (append result
1683 (cddr
1684 (adaptive-plot #'fun (car x-start) (car x-mid) (car x-end)
1685 (car y-start) (car y-mid) (car y-end)
1686 depth 1e-5)))
1687 (adaptive-plot #'fun (car x-start) (car x-mid) (car x-end)
1688 (car y-start) (car y-mid) (car y-end)
1689 depth 1e-5))))
1691 ;; Fix up out-of-range values
1692 ;; and clobber non-numeric values.
1694 (do ((x result (cddr x))
1695 (y (cdr result) (cddr y)))
1696 ((null y))
1697 (if (numberp (car y))
1698 ;; We can let graphic program do the clipping for us.
1699 ;; This results in better looking plots. For example:
1700 ;; plot2d(x-floor(x),[x,0,5], [y,0,.5])
1701 ;; has lines going all the way to
1702 ;; the limits. Previously, the lines would stop
1703 ;; before the limit.
1704 (unless (<= ymin (car y) ymax)
1705 (incf n-clipped))
1706 (progn
1707 (incf n-non-numeric)
1708 (setf (car x) 'moveto)
1709 (setf (car y) 'moveto)))
1710 (when (and (getf plot-options '$logx)
1711 (numberp (car x)))
1712 (setf (car x) (exp (car x))))
1714 (when (and (getf plot-options '$logy)
1715 (numberp (car y)))
1716 (setf (car y) (exp (car y)))))
1718 ;; Filter out any MOVETO's which do not precede a number.
1719 ;; Code elsewhere in this file expects MOVETO's to
1720 ;; come in pairs, so leave two MOVETO's before a number.
1721 (let ((n (length result)))
1722 (dotimes (i n)
1723 (when
1724 (and
1725 (evenp i)
1726 (eq (nth i result) 'moveto)
1727 (eq (nth (1+ i) result) 'moveto)
1728 (or
1729 (eq i (- n 2))
1730 (eq (nth (+ i 2) result) 'moveto)))
1731 (setf (nth i result) nil)
1732 (setf (nth (1+ i) result) nil))))
1734 (let ((result-sans-nil (delete nil result)))
1735 (if (null result-sans-nil)
1736 (cond
1737 ((= n-non-numeric 0)
1738 (mtell (intl:gettext "plot2d: all values will be clipped.~%")))
1739 ((= n-clipped 0)
1740 (mtell (intl:gettext "plot2d: expression evaluates to non-numeric value everywhere in plotting range.~%")))
1742 (mtell (intl:gettext "plot2d: all values are non-numeric, or clipped.~%"))))
1743 (progn
1744 (if (> n-non-numeric 0)
1745 (mtell (intl:gettext "plot2d: expression evaluates to non-numeric value somewhere in plotting range.~%")))
1746 (if (> n-clipped 0)
1747 (mtell (intl:gettext "plot2d: some values will be clipped.~%")))))
1748 (cons '(mlist) result-sans-nil))))))
1750 (defun get-range (lis)
1751 (let ((ymin +most-positive-flonum+)
1752 (ymax +most-negative-flonum+))
1753 (declare (type flonum ymin ymax))
1754 (do ((l lis (cddr l)))
1755 ((null l))
1756 (or (floatp (car l)) (setf (car l) (float (car l))))
1757 (cond ((< (car l) ymin)
1758 (setq ymin (car l))))
1759 (cond ((< ymax (car l))
1760 (setq ymax (car l)))))
1761 (list '(mlist) ymin ymax)))
1763 #+sbcl (defvar $gnuplot_view_args "-persist ~a")
1764 #-sbcl (defvar $gnuplot_view_args "-persist ~s")
1766 #+(or sbcl openmcl) (defvar $gnuplot_file_args "~a")
1767 #-(or sbcl openmcl) (defvar $gnuplot_file_args "~s")
1769 ;; random-file-name
1770 ;; Creates a random word of 'count' alphanumeric characters
1771 (defun random-name (count)
1772 (let ((chars "0123456789abcdefghijklmnopqrstuvwxyz") (name ""))
1773 (setf *random-state* (make-random-state t))
1774 (dotimes (i count)
1775 (setq name (format nil "~a~a" name (aref chars (random 36)))))
1776 name))
1778 ;; TODO: This next function should be moved into gnuplot_def.lisp
1779 ;; and instead of the list of options, the argument should be the desired
1780 ;; extension for the file (villate 20240325)
1781 (defun plot-set-gnuplot-script-file-name (options)
1782 (let ((gnuplot-term (getf options '$gnuplot_term))
1783 (gnuplot-out-file (getf options '$gnuplot_out_file)))
1784 (if (and (find (getf options '$plot_format) '($gnuplot_pipes $gnuplot))
1785 (eq gnuplot-term '$default) gnuplot-out-file)
1786 (plot-file-path gnuplot-out-file t options)
1787 (plot-file-path (format nil "~a.~a" (random-name 16)
1788 (ensure-string (getf options '$plot_format)))
1789 nil options))))
1791 (defun plot-temp-file0 (file &optional (preserve-file nil))
1792 (let ((filename
1793 (if *maxima-tempdir*
1794 (format nil "~a/~a" *maxima-tempdir* file)
1795 file)))
1796 (unless preserve-file
1797 (setf (gethash filename *temp-files-list*) t))
1798 (format nil "~a" filename)
1800 (defun plot-temp-file (file &optional (preserve-file nil) (plot-options nil))
1801 (let (script-name
1802 (script-name-or-fun
1803 (and plot-options (getf plot-options '$gnuplot_script_file))))
1804 (if (null script-name-or-fun)
1805 (plot-temp-file0 file preserve-file)
1806 (progn
1807 (setq
1808 script-name
1809 (cond
1810 ((symbolp script-name-or-fun) (mfuncall script-name-or-fun file))
1811 (t script-name-or-fun)))
1812 (if (pathname-directory script-name)
1813 script-name
1814 (plot-temp-file0 script-name preserve-file))))))
1816 ;; If no file path is given, uses temporary directory path
1817 (defun plot-file-path (file &optional (preserve-file nil) (plot-options nil))
1818 (if (pathname-directory file)
1819 file
1820 (plot-temp-file file preserve-file plot-options)))
1822 (defun gnuplot-process (plot-options &optional file out-file)
1823 (let ((gnuplot-term (getf plot-options '$gnuplot_term))
1824 (run-viewer (getf plot-options '$run_viewer))
1825 #-(or (and sbcl win32) (and sbcl win64) (and ccl windows))
1826 (gnuplot-preamble
1827 (string-downcase (getf plot-options '$gnuplot_preamble))))
1829 ;; creates the output file, when there is one to be created
1830 (when (and out-file (not (eq gnuplot-term '$default)))
1831 #+(or (and sbcl win32) (and sbcl win64) (and ccl windows))
1832 ($system $gnuplot_command (format nil $gnuplot_file_args file))
1833 #-(or (and sbcl win32) (and sbcl win64) (and ccl windows))
1834 ($system (format nil "~a ~a" $gnuplot_command
1835 (format nil $gnuplot_file_args file))))
1837 ;; displays contents of the output file, when gnuplot-term is dumb,
1838 ;; or runs gnuplot when gnuplot-term is default
1839 (when run-viewer
1840 (case gnuplot-term
1841 ($default
1842 ;; the options given to gnuplot will be different when the user
1843 ;; redirects the output by using "set output" in the preamble
1844 #+(or (and sbcl win32) (and sbcl win64) (and ccl windows))
1845 ($system $gnuplot_command "-persist" (format nil $gnuplot_file_args file))
1846 #-(or (and sbcl win32) (and sbcl win64) (and ccl windows))
1847 ($system
1848 (format nil "~a ~a" $gnuplot_command
1849 (format nil (if (search "set out" gnuplot-preamble)
1850 $gnuplot_file_args $gnuplot_view_args)
1851 file))))
1852 ($dumb
1853 (if out-file
1854 ($printfile (car out-file))
1855 (merror (intl:gettext "plotting: option 'gnuplot_out_file' not defined."))))))))
1857 ;; PLOT OPTIONS PARSING
1858 ;; plot-options-parser puts the plot options given into a property list.
1859 ;; maxopts: a list (not a Maxima list!) with plot options.
1860 ;; options: a property list, or an empty list.
1861 ;; Example:
1862 ;; (plot-options-parser (list #$[x,-2,2]$ #$[nticks,30]$) '($xlabel "t"))
1863 ;; returns:
1864 ;; ($NTICKS 30 $X (-2.0 2.0) $XLABEL "t")
1866 (defun plot-options-parser (maxopts options &aux name)
1867 (dolist (opt maxopts)
1868 (unless (or ($listp opt) (symbolp opt))
1869 (merror
1870 (intl:gettext
1871 "plot-options-parser: option \"~M\" should be a list or a symbol")
1872 opt))
1873 (cond
1874 (($listp opt)
1875 (unless ($symbolp (setq name (second opt)))
1876 (merror
1877 (intl:gettext
1878 "plot-options-parser: Expecting option name as a symbol, found: \"~M\"")
1879 opt))
1880 (case name
1881 ($adapt_depth
1882 (setf (getf options '$adapt_depth)
1883 (check-option (cdr opt) #'(lambda (n)
1884 ;; N should be a non-negative integer
1885 (and (integerp n)
1886 (>= n 0)))
1887 "a non-negative integer" 1)))
1888 ($axes (setf (getf options '$axes)
1889 (check-option-b (cdr opt) #'axesoptionp "x, y, solid" 1)))
1890 ($azimuth (if (caddr opt)
1891 (setf (caddr opt) (parse-azimuth (caddr opt))))
1892 (setf (getf options '$azimuth)
1893 (check-option (cdr opt) #'realp "a real number" 1)))
1894 ($box (setf (getf options '$box)
1895 (check-option-boole (cdr opt))))
1896 ($color (setf (getf options '$color)
1897 (check-option (cdr opt) #'plotcolorp "a color")))
1898 ($color_bar (setf (getf options '$color_bar)
1899 (check-option-boole (cdr opt))))
1900 ($color_bar_tics
1901 (if (cddr opt)
1902 (setf (cddr opt) (mapcar #'coerce-float (cddr opt))))
1903 (setf (getf options '$color_bar_tics)
1904 (check-option-b (cdr opt) #'realp "a real number" 3)))
1905 ($elevation (if (caddr opt)
1906 (setf (caddr opt) (parse-elevation (caddr opt))))
1907 (setf (getf options '$elevation)
1908 (check-option (cdr opt) #'realp "a real number" 1)))
1909 ($grid (setf (getf options '$grid)
1910 (check-option (cdr opt) #'naturalp "a natural number" 2)))
1911 ($grid2d (setf (getf options '$grid2d)
1912 (check-option-boole (cdr opt))))
1913 ($iterations
1914 (setf (getf options '$iterations)
1915 (check-option (cdr opt) #'naturalp "a natural number" 1)))
1916 ($label (setf (getf options '$label)
1917 (check-option-label (cdr opt))))
1918 ($legend (setf (getf options '$legend)
1919 (let ((x (check-option-b (cdr opt) #'stringp "a string")))
1920 (if (listp x) x (cons x nil)))))
1921 ($levels (setf (getf options '$levels)
1922 (check-option-levels (cdr opt))))
1923 ($logx (setf (getf options '$logx)
1924 (check-option-boole (cdr opt))))
1925 ($logy (setf (getf options '$logy)
1926 (check-option-boole (cdr opt))))
1927 ($mesh_lines_color
1928 (setf (getf options '$mesh_lines_color)
1929 (check-option-b (cdr opt) #'plotcolorp "a color" 1)))
1930 ($nticks (setf (getf options '$nticks)
1931 (check-option (cdr opt) #'naturalp "a natural number" 1)))
1932 ($palette (setf (getf options '$palette)
1933 (check-option-palette (cdr opt))))
1934 ($plotepsilon (setf (getf options '$plotepsilon)
1935 (check-option (cdr opt) #'realp "a real number" 1)))
1936 ($plot_format (setf (getf options '$plot_format)
1937 (check-option-format (cdr opt))))
1938 ($plot_realpart (setf (getf options '$plot_realpart)
1939 (check-option-boole (cdr opt))))
1940 ($point_type (setf (getf options '$point_type)
1941 (check-option (cdr opt) #'pointtypep "a point type")))
1942 ($pdf_file (setf (getf options '$pdf_file)
1943 (check-option (cdr opt) #'stringp "a string" 1)))
1944 ($png_file (setf (getf options '$png_file)
1945 (check-option (cdr opt) #'stringp "a string" 1)))
1946 ($ps_file (setf (getf options '$ps_file)
1947 (check-option (cdr opt) #'stringp "a string" 1)))
1948 ($run_viewer (setf (getf options '$run_viewer)
1949 (check-option-boole (cdr opt))))
1950 ($same_xy (setf (getf options '$same_xy)
1951 (check-option-boole (cdr opt))))
1952 ($same_xyz (setf (getf options '$same_xyz)
1953 (check-option-boole (cdr opt))))
1954 ($sample (setf (getf options '$sample)
1955 (check-option (cdr opt) #'naturalp "a natural number" 2)))
1956 ($style (setf (getf options '$style)
1957 (check-option-style (cdr opt))))
1958 ($svg_file (setf (getf options '$svg_file)
1959 (check-option (cdr opt) #'stringp "a string" 1)))
1960 ($t (setf (getf options '$t) (cddr (check-range opt))))
1961 ($title (setf (getf options '$title)
1962 (check-option (cdr opt) #'stringp "a string" 1)))
1963 ($transform_xy (setf (getf options '$transform_xy)
1964 (check-option-b (cdr opt) #'functionp "a function make_transform" 1)))
1965 ($window (setf (getf options '$window)
1966 (check-option (cdr opt)
1967 #'(lambda (n) (and (integerp n) (>= n 0)))
1968 "a non-negative integer" 1)))
1969 ($x (setf (getf options '$x) (cddr (check-range opt))))
1970 ($xbounds (setf (getf options '$xbounds) (cddr (check-range opt))))
1971 ($xlabel (setf (getf options '$xlabel)
1972 (check-option (cdr opt) #'string "a string" 1)))
1973 ($xtics
1974 (if (cddr opt)
1975 (setf (cddr opt) (mapcar #'coerce-float (cddr opt))))
1976 (setf (getf options '$xtics)
1977 (check-option-b (cdr opt) #'realp "a real number" 3)))
1978 ($xy_scale
1979 (if (cddr opt)
1980 (setf (cddr opt) (mapcar #'coerce-float (cddr opt))))
1981 (setf (getf options '$xy_scale)
1982 (check-option (cdr opt) #'realpositivep
1983 "a positive real number" 2)))
1984 ($y (setf (getf options '$y) (cddr (check-range opt))))
1985 ($ybounds (setf (getf options '$ybounds) (cddr (check-range opt))))
1986 ($ylabel (setf (getf options '$ylabel)
1987 (check-option (cdr opt) #'string "a string" 1)))
1988 ($ytics
1989 (if (cddr opt)
1990 (setf (cddr opt) (mapcar #'coerce-float (cddr opt))))
1991 (setf (getf options '$ytics)
1992 (check-option-b (cdr opt) #'realp "a real number" 3)))
1993 ($yx_ratio
1994 (if (caddr opt)
1995 (setf (caddr opt) (coerce-float (caddr opt))))
1996 (setf (getf options '$yx_ratio)
1997 (check-option (cdr opt) #'realp "a real number" 1)))
1998 ($z (setf (getf options '$z) (cddr (check-range opt))))
1999 ($zlabel (setf (getf options '$zlabel)
2000 (check-option (cdr opt) #'string "a string" 1)))
2001 ($zmin
2002 (if (caddr opt)
2003 (setf (caddr opt) (coerce-float (caddr opt))))
2004 (setf (getf options '$zmin)
2005 (check-option-b (cdr opt) #'realp "a real number" 1)))
2006 ($ztics
2007 (if (cddr opt)
2008 (setf (cddr opt) (mapcar #'coerce-float (cddr opt))))
2009 (setf (getf options '$ztics)
2010 (check-option-b (cdr opt) #'realp "a real number" 3)))
2011 ($gnuplot_4_0 (setf (getf options '$gnuplot_4_0)
2012 (check-option-boole (cdr opt))))
2013 ($gnuplot_curve_titles
2014 (setf (getf options '$gnuplot_curve_titles)
2015 (check-option (cdr opt) #'stringp "a string")))
2016 ($gnuplot_curve_styles
2017 (setf (getf options '$gnuplot_curve_styles)
2018 (check-option (cdr opt) #'stringp "a string")))
2019 ($gnuplot_default_term_command
2020 (setf (getf options '$gnuplot_default_term_command)
2021 (check-option (cdr opt) #'stringp "a string" 1)))
2022 ($gnuplot_dumb_term_command
2023 (setf (getf options '$gnuplot_dumb_term_command)
2024 (check-option (cdr opt) #'stringp "a string" 1)))
2025 ($gnuplot_out_file
2026 (setf (getf options '$gnuplot_out_file)
2027 (check-option (cdr opt) #'stringp "a string" 1)))
2028 ($gnuplot_script_file
2029 (setf (getf options '$gnuplot_script_file)
2030 (check-option (cdr opt) #'(lambda(x) (or (stringp x) (symbolp x))) "a string or symbol" 1)
2031 (getf options '$plot_format) '$gnuplot))
2032 ($gnuplot_pm3d
2033 (setf (getf options '$gnuplot_pm3d)
2034 (check-option-boole (cdr opt))))
2035 ($gnuplot_strings
2036 (setf (getf options '$gnuplot_strings)
2037 (check-option-boole (cdr opt))))
2038 ($gnuplot_svg_background
2039 (setf (getf options '$gnuplot_svg_background)
2040 (check-option-b (cdr opt) #'stringp "a string" 1)))
2041 ($gnuplot_preamble
2042 (setf (getf options '$gnuplot_preamble)
2043 (check-option (cdr opt) #'stringp "a string" 1)))
2044 ($gnuplot_postamble
2045 (setf (getf options '$gnuplot_postamble)
2046 (check-option (cdr opt) #'stringp "a string" 1)))
2047 ($gnuplot_pdf_term_command
2048 (setf (getf options '$gnuplot_pdf_term_command)
2049 (check-option (cdr opt) #'stringp "a string" 1)))
2050 ($gnuplot_png_term_command
2051 (setf (getf options '$gnuplot_png_term_command)
2052 (check-option (cdr opt) #'stringp "a string" 1)))
2053 ($gnuplot_ps_term_command
2054 (setf (getf options '$gnuplot_ps_term_command)
2055 (check-option (cdr opt) #'stringp "a string" 1)))
2056 ($gnuplot_svg_term_command
2057 (setf (getf options '$gnuplot_svg_term_command)
2058 (check-option (cdr opt) #'stringp "a string" 1)))
2059 ;; gnuplot_term is a tricky one: when it is just default, dumb or
2060 ;; ps, we want it to be a symbol, but when it is more complicated,
2061 ;; i.e. "ps; size 16cm, 12cm", it must be a string and not a symbol
2062 ($gnuplot_term
2063 (let ((s (caddr opt)))
2064 (when (stringp s)
2065 (cond ((string= s "default") (setq s '$default))
2066 ((string= s "dumb") (setq s '$dumb))
2067 ((string= s "ps") (setq s '$ps))))
2068 (if (atom s)
2069 (setf (getf options '$gnuplot_term) s)
2070 (merror
2071 (intl:gettext "Wrong argument for plot option \"gnuplot_term\". Expecting a string or a symbol but found \"~M\".") s))))
2073 (merror
2074 (intl:gettext "plot-options-parser: unknown plot option: ~M") opt))))
2075 ((symbolp opt)
2076 (case opt
2077 ($axes (setf (getf options '$axes) t))
2078 ($box (setf (getf options '$box) t))
2079 ($color_bar (setf (getf options '$color_bar) t))
2080 ($color_bar_tics (remf options '$color_bar_tics))
2081 ($grid2d (setf (getf options '$grid2d) t))
2082 ($legend (remf options '$legend))
2083 ($mesh_lines_color (remf options '$mesh_lines_color))
2084 ($logx (setf (getf options '$logx) t))
2085 ($logy (setf (getf options '$logy) t))
2086 ($palette (remf options '$palette))
2087 ($plot_realpart (setf (getf options '$plot_realpart) t))
2088 ($run_viewer (setf (getf options '$run_viewer) t))
2089 ($same_xy (setf (getf options '$same_xy) t))
2090 ($same_xyz (setf (getf options '$same_xyz) t))
2091 ($xtics (remf options '$xtics))
2092 ($ytics (remf options '$ytics))
2093 ($zmin (remf options '$zmin))
2094 ($gnuplot_4_0 (setf (getf options '$gnuplot_4_0) t))
2095 ($gnuplot_pm3d (setf (getf options '$gnuplot_pm3d) t))
2096 ($gnuplot_strings (setf (getf options '$gnuplot_strings) t))
2097 ($gnuplot_svg_background (setf (getf options '$gnuplot_svg_background) t))
2098 ($noaxes (setf (getf options '$axes) nil))
2099 ($nobox (setf (getf options '$box) nil))
2100 ($nocolor_bar (setf (getf options '$color_bar) nil))
2101 ($nocolor_bat_tics (setf (getf options '$color_bat_tics) nil))
2102 ($nogrid2d (setf (getf options '$grid2d) nil))
2103 ($nolegend (setf (getf options '$legend) nil))
2104 ($nologx (setf (getf options '$logx) nil))
2105 ($nology (setf (getf options '$logy) nil))
2106 ($nomesh_lines (setf (getf options '$mesh_lines_color) nil))
2107 ($nopalette (setf (getf options '$palette) nil))
2108 ($noplot_realpart (setf (getf options '$plot_realpart) nil))
2109 ($norun_viewer (setf (getf options '$run_viewer) nil))
2110 ($nosame_xy (setf (getf options '$same_xy) nil))
2111 ($nosame_xyz (setf (getf options '$same_xyz) nil))
2112 ($notransform_xy (remf options '$transform_xy))
2113 ($noxtics (setf (getf options '$xtics) nil))
2114 ($noytics (setf (getf options '$ytics) nil))
2115 ($noztics (setf (getf options '$ztics) nil))
2116 ($nognuplot_strings (setf (getf options '$gnuplot_strings) nil))
2117 ($nognuplot_svg_background (setf (getf options '$gnuplot_svg_background) nil))
2119 (merror (intl:gettext "Unknown plot option \"~M\".") opt))))))
2120 ;; plots that use ASCII art should not use gnuplot_pipes
2121 (when (and (eq (getf options '$plot_format) '$gnuplot_pipes)
2122 (eq (getf options '$gnuplot_term) '$dumb))
2123 (setf (getf options '$plot_format) '$gnuplot))
2124 options)
2126 ;; natural numbers predicate
2127 (defun naturalp (n) (or (and (integerp n) (> n 0)) nil))
2129 ;; positive real numbers predicate
2130 (defun realpositivep (x) (or (and (realp x) (> x 0)) nil))
2132 ;; possible values for the axes option
2133 (defun axesoptionp (o) (if (member o '($x $y $solid)) t nil))
2135 ;; the 13 possibilities for the point types
2136 (defun pointtypep (p)
2137 (if (member p '($bullet $circle $plus $times $asterisk $box $square
2138 $triangle $delta $wedge $nabla $diamond $lozenge)) t nil))
2140 ;; Colors can only be one of the named colors or a six-digit hexadecimal
2141 ;; number with a # suffix.
2142 (defun plotcolorp (color)
2143 (cond ((and (stringp color)
2144 (string= (subseq color 0 1) "#")
2145 (= (length color) 7)
2146 (ignore-errors (parse-integer (subseq color 1 6) :radix 16)))
2148 ((member color '($red $green $blue $magenta $cyan $yellow
2149 $orange $violet $brown $gray $black $white))
2151 (t nil)))
2153 ;; tries to convert az into a floating-point number between 0 and 360
2154 (defun parse-azimuth (az) (mod (coerce-float (meval* az)) 360))
2156 ;; tries to convert el into a floating-poitn number between -180 and 180
2157 (defun parse-elevation (el) (- (mod (+ 180 (coerce-float (meval* el))) 360) 180))
2159 ;; The following functions check the value of an option returning an atom
2160 ;; when there is only one argument or a list when there are several arguments
2162 ;; Checks for one or more items of the same type, using the test given.
2163 ;; If count is given, the number of arguments must be exactly count.
2164 (defun check-option (option test type &optional count)
2165 (when count
2166 (unless (= (1- (length option)) count)
2167 (merror
2168 (intl:gettext
2169 "Wrong number of arguments for plot option \"~M\". Expecting ~M but found ~M.")
2170 (car option) count (1- (length option)))))
2171 (dolist (item (cdr option))
2172 (when (not (funcall test item))
2173 (merror
2174 (intl:gettext "Wrong argument for plot option \"~M\". Expecting ~M but found \"~M\".") (car option) type item)))
2175 (if (= (length option) 2)
2176 (cadr option)
2177 (cdr option)))
2179 ;; Accepts one or more items of the same type or false.
2180 ;; When given, count is the maximum number of items.
2181 (defun check-option-b (option test type &optional count)
2182 (let ((n (- (length option) 1)))
2183 (when count
2184 (unless (< n (1+ count))
2185 (merror
2186 (intl:gettext
2187 "Plot option ~M must have ~M arguments, not ~M.")
2188 (car option) count (1- (length option)))))
2189 (cond
2190 ((= n 0)
2191 (merror
2192 (intl:gettext
2193 "Option ~M should be given arguments, or called by its name (no lists)")
2194 option))
2195 ((= n 1)
2196 (if (or (funcall test (cadr option)) (null (cadr option))
2197 (eq (cadr option) t))
2198 (cadr option)
2199 (merror
2200 (intl:gettext
2201 "Value of option ~M. should be ~M or false, not \"~M\".")
2202 (car option) type (cadr option))))
2203 ((> n 1)
2204 (dotimes (i n)
2205 (unless (funcall test (nth (+ i 1) option))
2206 (merror
2207 (intl:gettext
2208 "Value of option ~M should be ~M, not \"~M\".")
2209 (car option) type (nth (+ i 1) option))))
2210 (cdr option)))))
2212 ;; Boolean options can be [option], [option,true] or [option,false]
2213 (defun check-option-boole (option)
2214 (if (= 1 (length option))
2216 (if (and (= 2 (length option))
2217 (or (eq (cadr option) t) (null (cadr option))))
2218 (cadr option)
2219 (merror (intl:gettext "plot option ~M must be either true or false.")
2220 (car option)))))
2222 ;; label can be either [label, string, real, real] or
2223 ;; [label, [string_1, real, real],...,[string_n, real, real]]
2224 (defun check-option-label (option &aux opt)
2225 (if (not ($listp (cadr option)))
2226 (setq opt (list (cons '(mlist) (cdr option))))
2227 (setq opt (cdr option)))
2228 (dolist (item opt)
2229 (when (not (and ($listp item) (= 4 (length item)) (stringp (second item))
2230 (realp (setf (third item) (coerce-float (third item))))
2231 (realp (setf (fourth item) (coerce-float (fourth item))))))
2232 (merror
2233 (intl:gettext
2234 "Wrong argument ~M for option ~M. Must be either [label,\"text\",x,y] or [label, [\"text 1\",x1,y1],...,[\"text n\",xn,yn]]")
2235 item (car option))))
2236 opt)
2238 ;; one of the possible formats
2239 (defun check-option-format (option &aux formats)
2240 (setq formats '($geomview $gnuplot $gnuplot_pipes $mgnuplot $xmaxima))
2241 (unless (member (cadr option) formats)
2242 (merror
2243 (intl:gettext
2244 "Wrong argument ~M for option ~M. Must one of the following symbols: geomview, gnuplot, mgnuplot, xmaxima (or gnuplot_pipes in Unix)")
2245 (cadr option) (car option)))
2246 (cadr option))
2248 ;; palette most be one or more Maxima lists starting with the name of one
2249 ;; of the 5 kinds: hue, saturation, value, gray or gradient. The first
2250 ;; four types must be followed by 4 floating-point numbers, while the
2251 ;; gradient type must be followed by a list of valid colors.
2252 (defun check-option-palette (option)
2253 (if (and (= (length option) 2) (null (cadr option)))
2255 (progn
2256 (dolist (item (cdr option))
2257 (when (not (and ($listp item)
2258 (member (cadr item)
2259 '($hue $saturation $value $gray $gradient))))
2260 (merror
2261 (intl:gettext
2262 "Wrong argument ~M for option ~M. Not a valid palette.")
2263 item (car option)))
2264 (if (eq (cadr item) '$gradient)
2265 (dolist (c (cddr item))
2266 (unless (plotcolorp c)
2267 (merror
2268 (intl:gettext
2269 "In palette option, ~M is not a valid color")
2270 c)))
2271 (progn
2272 (setf (cddr item) (mapcar #'coerce-float (cddr item)))
2273 (check-option (cdr item) #'realp "a real number" 4))))
2274 (cdr option))))
2276 ;; style can be one or several of the names of the styles or one or several
2277 ;; Maxima lists starting with the name of one of the styles.
2278 (defun check-option-style (option)
2279 (if (and (= (length option) 2) (null (cadr option)))
2281 (progn
2282 (let (name parsed)
2283 (dolist (item (cdr option))
2284 (if ($listp item)
2285 (setq name (second item))
2286 (setq name item))
2287 (when (not (member name
2288 '($lines $points $linespoints $dots $impulses)))
2289 (merror
2290 (intl:gettext
2291 "Wrong argument ~M for option ~M. Not a valid style")
2292 name (car option)))
2293 (setq parsed (cons item parsed)))
2294 (reverse parsed)))))
2296 ;; Transform can be false or the name of a function for the transformation.
2297 (defun check-option-transform (option)
2298 (if (and (= (length option) 2)
2299 (or (atom (cadr option)) (null (cadr option))))
2300 (cadr option)
2301 (merror
2302 (intl:gettext
2303 "Wrong argument ~M for option ~M. Should be either false or the name of function for the transformation") option (car option))))
2305 ;; levels can be a single natural number (requested number of levels)
2306 ;; or two or more floating-point numbers.
2307 (defun check-option-levels (option)
2308 (cond
2309 ((< (length option) 3)
2310 (check-option option #'naturalp "a natural number" 1))
2312 (mapcar #'coerce-float (cdr option))
2313 (check-option option #'realp "a real number" (1- (length option))))))
2315 ;; Tries to get n numbers between fmin and fmax of the form d*10^e,
2316 ;; where d is either 1, 2 or 5.
2317 ;; It returns a list with n or less numbers
2318 ;; (adapted from procedure getticks of Xmaxima)
2320 (defun getlevels (fmin fmax n)
2321 (let ((len (- fmax fmin)) (best 0) levels val fac j1 j2 ans)
2322 (dolist (v '(0.1 0.2 0.5))
2323 (setq val (ceiling (/ (log (/ len n v)) (log 10))))
2324 (setq fac (/ 1 v (expt 10 val)))
2325 (setq j1 (ceiling (* fmin fac)))
2326 (setq j2 (floor (* fmax fac)))
2327 (setq levels nil)
2328 (do ((j j1 (1+ j))) ((> j j2))
2329 (push (/ j fac) levels))
2330 (when (> (length levels) best)
2331 (setq best (length levels))
2332 (setq ans (copy-list levels))))
2333 (reverse ans)))
2335 #| plot2d
2336 Examples:
2338 plot2d (sec(x), [x, -2, 2], [y, -20, 20]);
2340 plot2d (exp(3*s), [s, -2, 2], logy);
2342 plot2d ([parametric, cos(t), sin(t), [t, -%pi, %pi]], same_xy);
2344 xy:[[10,.6], [20,.9], [30,1.1], [40,1.3], [50,1.4]]$
2345 plot2d ( [ [discrete, xy], 2*%pi*sqrt(l/980) ], [l, 0, 50],
2346 [style, points, lines], [color, red, blue], [point_type, box],
2347 [legend, "experiment", "theory"],
2348 [xlabel, "pendulum's length (cm)"], [ylabel, "period (s)"]);
2350 plot2d ( x^2-1, [x, -3, 3], [y, -2, 10], nobox, [color, red],
2351 [ylabel, "x^2-1"], [plot_format, xmaxima]);
2353 plot2d ( x^2+y^2 = 1, [x, -2, 2], [y, -2 ,2]);
2355 (defmfun $plot2d
2356 (fun &optional xrange &rest extra-options
2357 &aux
2358 ($display2d nil) (*plot-realpart* *plot-realpart*)
2359 (options (copy-tree *plot-options*)) yrange output-file plot)
2360 ;; fun must be a maxima list with several objects: expressions (simple
2361 ;; functions), maxima lists (parametric or discrete cases).
2362 ;; A single parametric or discrete plot is placed inside a maxima list.
2363 (setf (getf options '$type) "plot2d")
2364 (when (and (consp fun)
2365 (or (eq (second fun) '$parametric)
2366 (eq (second fun) '$contour)
2367 (eq (second fun) '$discrete)))
2368 (setq fun `((mlist) ,fun)))
2369 ;; If by now fun is not a maxima list, it is then a single expression
2370 (unless ($listp fun ) (setq fun `((mlist) ,fun)))
2371 ;; 2- Get names for the two axis and values for xmin and xmax if needed.
2372 ;; If any of the objects in the fun list is a simple function,
2373 ;; the xrange option is mandatory and will provide the name of
2374 ;; the horizontal axis and the values of xmin and xmax.
2375 (let ((xrange-required nil) (bounds-required nil) (yrange-required nil)
2376 small huge prange)
2377 #-clisp (setq small (- (/ +most-positive-flonum+ 1024)))
2378 #+clisp (setq small (- (/ most-positive-double-float 1024.0)))
2379 #-clisp (setq huge (/ +most-positive-flonum+ 1024))
2380 #+clisp (setq huge (/ most-positive-double-float 1024.0))
2381 (setf (getf options '$ybounds) (list small huge))
2382 (dolist (f (rest fun))
2383 (if ($listp f)
2384 (progn
2385 (case ($first f)
2386 ($parametric
2387 (unless bounds-required
2388 (setq bounds-required t)
2389 ;; Default X and Y bound large so parametric plots don't get
2390 ;; prematurely clipped. Don't use most-positive-flonum
2391 ;; because draw2d will overflow.
2392 (setf (getf options '$xbounds) (list small huge)))
2393 (setq prange (check-range ($fourth f))))
2394 ($contour
2395 (setq xrange (check-range xrange))
2396 (setq xrange-required t)
2397 (unless yrange-required
2398 (setq yrange-required t)
2399 (if (null extra-options)
2400 (merror
2401 (intl:gettext "plot2d: Missing interval for variable 2."))
2402 (progn
2403 (setq yrange (pop extra-options))
2404 (setq yrange (check-range yrange))
2405 (setf (getf options '$xvar) ($first xrange))
2406 (setf (getf options '$yvar) ($first yrange))
2407 (setf (getf options '$x) (cddr xrange))
2408 (setf (getf options '$y) (cddr yrange))))))
2409 ($discrete)
2411 (merror
2412 (intl:gettext
2413 "plot2d: a keyword 'parametric' or 'discrete' missing in ~M")
2414 f))))
2415 ;; The expression represents a function, explicit or implicit
2416 (progn
2417 (unless xrange-required
2418 (setq xrange-required t)
2419 (setq xrange (check-range xrange))
2420 (setq xrange-required t)
2421 (unless (getf options '$xlabel)
2422 (setf (getf options '$xlabel) (ensure-string (second xrange))))
2423 (setf (getf options '$xvar) (cadr xrange))
2424 (setf (getf options '$x) (cddr xrange)))
2425 (when (and (listp f) (eq 'mequal (caar f)))
2426 ;; Implicit function
2427 (unless yrange-required
2428 (setq yrange-required t)
2429 (if (null extra-options)
2430 (merror
2431 (intl:gettext "plot2d: Missing interval for variable 2."))
2432 (progn
2433 (setq yrange (pop extra-options))
2434 (setq yrange (check-range yrange))
2435 (setf (getf options '$yvar) ($first yrange))
2436 (setf (getf options '$y) (cddr yrange)))))))))
2437 (when (not xrange-required)
2438 ;; Make the default ranges on X nd Y large so parametric plots
2439 ;; don't get prematurely clipped. Don't use most-positive-flonum
2440 ;; because draw2d will overflow.
2441 (setf (getf options '$xbounds) (list small huge))
2442 (when xrange
2443 ;; second argument was really a plot option, not an xrange
2444 (setq extra-options (cons xrange extra-options)))))
2445 ;; If no global options xlabel or ylabel have been given, choose
2446 ;; a default value for them: the expressions given, converted
2447 ;; to Maxima strings, if their length is less than 50 characters,
2448 ;; or the default "x" and "y" otherwise.
2449 (when (= (length fun) 2)
2450 (let ((v (second fun)) xlabel ylabel)
2451 (cond ((atom v)
2452 (setq xlabel "x") (setq ylabel ($sconcat v)))
2453 ((eq (second v) '$parametric)
2454 (setq xlabel ($sconcat (third v)))
2455 (setq ylabel ($sconcat (fourth v))))
2456 ((eq (second v) '$discrete)
2457 (setq xlabel "x") (setq ylabel "y"))
2458 ((eq (second v) '$contour)
2459 (setq xlabel (ensure-string (getf options '$xvar)))
2460 (setq ylabel (ensure-string (getf options '$yvar))))
2462 (setq xlabel "x") (setq ylabel ($sconcat v))))
2463 (unless (getf options '$xlabel)
2464 (if (< (length xlabel) 50) (setf (getf options '$xlabel) xlabel)))
2465 (unless (getf options '$ylabel)
2466 (if (< (length ylabel) 50) (setf (getf options '$ylabel) ylabel)))))
2467 ;; For explicit functions, default ylabel is the name of the 2nd variable
2468 (when (getf options '$yvar)
2469 (setf (getf options '$ylabel) ($sconcat (getf options '$yvar))))
2470 ;; Parse the given options into the options list
2471 (setq options (plot-options-parser extra-options options))
2472 (when (getf options '$y) (setf (getf options '$ybounds) (getf options '$y)))
2473 ;; Remove axes labels when no box is used in gnuplot
2474 (when (and (member '$box options) (not (getf options '$box))
2475 (not (eq (getf options '$plot_format) '$xmaxima)))
2476 (remf options '$xlabel)
2477 (remf options '$ylabel))
2478 ;; check options given
2479 (let ((xmin (first (getf options '$x))) (xmax (second (getf options '$x))))
2480 (when
2481 (and (getf options '$logx) xmin xmax)
2482 (if (> xmax 0)
2483 (when (<= xmin 0)
2484 (let ((revised-xmin (/ xmax 1000)))
2485 (mtell
2486 (intl:gettext
2487 "plot2d: lower bound must be positive when using 'logx'.~%plot2d: assuming lower bound = ~M instead of ~M")
2488 revised-xmin xmin)
2489 (setf (getf options '$x) (list revised-xmin xmax))
2490 (setq xrange `((mlist) ,(second xrange) ,revised-xmin ,xmax))))
2491 (merror
2492 (intl:gettext
2493 "plot2d: upper bound must be positive when using 'logx'; found: ~M")
2494 xmax))))
2495 (let ((ymin (first (getf options '$y)))
2496 (ymax (second (getf options '$y))))
2497 (when (and (getf options '$logy) ymin ymax)
2498 (if (> ymax 0)
2499 (when (<= ymin 0)
2500 (let ((revised-ymin (/ ymax 1000)))
2501 (mtell
2502 (intl:gettext
2503 "plot2d: lower bound must be positive when using 'logy'.~%plot2d: assuming lower bound = ~M instead of ~M")
2504 revised-ymin ymin)
2505 (setf (getf options '$y) (list revised-ymin ymax))))
2506 (merror
2507 (intl:gettext
2508 "plot2d: upper bound must be positive when using 'logy'; found: ~M")
2509 ymax))))
2510 (setq *plot-realpart* (getf options '$plot_realpart))
2511 ;; Creates the object that will be passed to the external graphic program
2512 (case (getf options '$plot_format)
2513 ($xmaxima
2514 (setq plot (make-instance 'xmaxima-plot)))
2515 ($gnuplot
2516 (setq plot (make-instance 'gnuplot-plot)))
2517 ($gnuplot_pipes
2518 (setq plot (make-instance 'gnuplot-plot))
2519 (setf (slot-value plot 'pipe) T))
2521 (merror (intl:gettext "plot2d: plot format ~M not supported")
2522 (getf options '$plot_format))))
2523 ;; Parse plot object and pass it to the graphic program
2524 (setq output-file (plot-preamble plot options))
2525 (plot2d-command plot fun options xrange)
2526 (plot-shipout plot options output-file))
2528 (defun msymbolp (x)
2529 (and (symbolp x) (char= (char (symbol-value x) 0) #\$)))
2531 (defmfun $tcl_output (lis i &optional (skip 2))
2532 (when (not (typep i 'fixnum))
2533 (merror
2534 (intl:gettext "tcl_ouput: second argument must be an integer; found ~M")
2536 (when (not ($listp lis))
2537 (merror
2538 (intl:gettext "tcl_output: first argument must be a list; found ~M") lis))
2539 (format *standard-output* "~% {")
2540 (cond (($listp (second lis))
2541 (loop for v in lis
2543 (format *standard-output* "~,,,,,,'eg " (nth i v))))
2545 (setq lis (nthcdr i lis))
2546 (loop with v = lis while v
2548 (format *standard-output* "~,,,,,,'eg " (car v))
2549 (setq v (nthcdr skip v)))))
2550 (format *standard-output* "~% }"))
2552 (defun tcl-output-list ( st lis )
2553 (cond ((null lis) )
2554 ((atom (car lis))
2555 (princ " { " st)
2556 (loop for v in lis
2557 count t into n
2558 when (eql 0 (mod n 5))
2559 do (terpri st)
2561 (format st "~,,,,,,'eg " v))
2562 (format st " }~%"))
2563 (t (tcl-output-list st (car lis))
2564 (tcl-output-list st (cdr lis)))))
2566 (defun check-range (range &aux tem a b)
2567 (or (and ($listp range)
2568 (setq tem (cdr range))
2569 (or (symbolp (car tem)) ($subvarp (car tem)))
2570 (numberp (setq a ($float (meval* (second tem)))))
2571 (numberp (setq b ($float (meval* (third tem)))))
2572 (< a b))
2573 (if range
2574 (merror
2575 (intl:gettext "plotting: range must be of the form [variable, min, max]; found: ~M")
2576 range)
2577 (merror
2578 (intl:gettext "plotting: no range given; must supply range of the form [variable, min, max]"))))
2579 `((mlist) ,(car tem) ,(float a) ,(float b)))
2581 (defmfun $zero_fun (x y) x y 0.0)
2583 (defun output-points (pl &optional m)
2584 "If m is supplied print blank line every m lines"
2585 (let ((j -1))
2586 (declare (fixnum j))
2587 (loop for i below (length (polygon-pts pl))
2588 with ar = (polygon-pts pl)
2589 do (print-pt (aref ar i))
2590 (setq i (+ i 1))
2591 (print-pt (aref ar i))
2592 (setq i (+ i 1))
2593 (print-pt (aref ar i))
2594 (terpri $pstream)
2595 (cond (m
2596 (setq j (+ j 1))
2597 (cond ((eql j (the fixnum m))
2598 (terpri $pstream)
2599 (setq j -1)))))
2602 (defun output-points-tcl (dest pl m)
2603 (format dest " {matrix_mesh ~%")
2604 ;; x y z are done separately:
2605 (loop for off from 0 to 2
2606 with ar = (polygon-pts pl)
2607 with i of-type fixnum = 0
2608 do (setq i off)
2609 (format dest "~%{")
2610 (loop
2611 while (< i (length ar))
2612 do (format dest "~% {")
2613 (loop for j to m
2614 do (print-pt (aref ar i))
2615 (setq i (+ i 3)))
2616 (format dest "}~%"))
2617 (format dest "}~%"))
2618 (format dest "}~%"))
2620 ;; contour_plot now punts to plot2d
2621 (defmfun $contour_plot (expr &rest optional-args)
2622 (let ((command "plot2d ([contour, "))
2623 (setq command ($sconcat command expr "]"))
2624 (when optional-args
2625 (dolist (arg optional-args)
2626 (setq command ($sconcat command ", " arg))))
2627 (setq command ($sconcat command ")"))
2628 (mtell (intl:gettext "contour_plot is now obsolete. Using plot2d instead:~%"))
2629 (mtell "~M~%" command)
2630 (apply #'$plot2d (cons `((mlist) $contour ,expr) optional-args))))
2632 #| plot3d
2633 Examples:
2635 plot3d (2^(-u^2 + v^2), [u, -3, 3], [v, -2, 2], [palette, false]);
2637 plot3d ( log ( x^2*y^2 ), [x, -2, 2], [y, -2, 2], [grid, 29, 29]);
2639 expr_1: cos(y)*(10.0+6*cos(x))$
2640 expr_2: sin(y)*(10.0+6*cos(x))$
2641 expr_3: -6*sin(x)$
2642 plot3d ([expr_1, expr_2, expr_3], [x, 0, 2*%pi], [y, 0, 2*%pi],
2643 ['grid, 40, 40], [z,-8,8]);
2645 plot3d (cos (-x^2 + y^3/4), [x, -4, 4], [y, -4, 4],
2646 [mesh_lines_color, false], [elevation, 0], [azimuth, 0], [grid, 150, 150]);
2648 spherical: make_transform ([th, phi,r], r*sin(phi)*cos(th),
2649 r*sin(phi)*sin(th), r*cos(phi))$
2650 plot3d ( 5, [th, 0, 2*%pi], [phi, 0, %pi], [transform_xy, spherical],
2651 [palette, [value, 0.65, 0.7, 0.1, 0.9]], [plot_format,xmaxima]);
2653 V: 1 / sqrt ( (x+1)^2+y^2 ) - 1 / sqrt( (x-1)^2+y^2 )$
2654 plot3d ( V, [x, -2, 2], [y, -2, 2], [z, -4, 4]);
2656 (defmfun $plot3d
2657 (fun &rest extra-options
2658 &aux
2659 lvars xrange yrange titles output-file functions exprn domain tem
2660 (options (copy-tree *plot-options*)) (*plot-realpart* *plot-realpart*)
2661 (usage (intl:gettext
2662 "plot3d: Usage.
2663 To plot a single function f of 2 variables v1 and v2:
2664 plot3d (f, [v1, min, max], [v2, min, max], options)
2665 A parametric representation of a surface with parameters v1 and v2:
2666 plot3d ([f1, f2, f3], [v1, min, max], [v2, min, max], options)
2667 Several functions depending on the two variables v1 and v2:
2668 plot3d ([f1, f2, ..., fn, [v1, min, max], [v2, min, max]], options)")))
2669 (setf (getf options '$type) "plot3d")
2670 ;; Ensure that fun is a list of expressions and maxima lists, followed
2671 ;; by a domain definition
2672 (if ($listp fun)
2673 (if (= 1 (length (check-list-plot3d fun)))
2674 ;; fun consisted of a single parametric expression
2675 (setq fun `(,fun ,(pop extra-options) ,(pop extra-options)))
2676 ;; fun was a maxima list with several independent surfaces
2677 (pop fun))
2678 ;; fun consisted of a single expression
2679 (setq fun `(,fun ,(pop extra-options) ,(pop extra-options))))
2680 ;; go through all the independent surfaces creating the functions stack
2681 (loop
2682 (setq exprn (pop fun))
2683 (if ($listp exprn)
2684 (progn
2685 (setq domain (check-list-plot3d exprn))
2686 (case (length domain)
2688 ;; exprn is a parametric representation of a surface
2689 (let (vars1 vars2 vars3)
2690 ;; list fun should have two valid ranges after exprn
2691 (setq xrange (check-range (pop fun)))
2692 (setq yrange (check-range (pop fun)))
2693 ;; list of the two variables for the parametric equations
2694 (setq lvars `((mlist),(second xrange) ,(second yrange)))
2695 ;; make sure that the 3 parametric equations depend only
2696 ;; on the two variables in lvars
2697 (setq vars1
2698 ($listofvars
2699 (mfuncall
2700 (coerce-float-fun (second exprn) lvars "plot3d")
2701 (second lvars) (third lvars))))
2702 (setq vars2
2703 ($listofvars
2704 (mfuncall
2705 (coerce-float-fun (third exprn) lvars "plot3d")
2706 (second lvars) (third lvars))))
2707 (setq vars3
2708 ($listofvars
2709 (mfuncall
2710 (coerce-float-fun (fourth exprn) lvars "plot3d")
2711 (second lvars) (third lvars))))
2712 (setq lvars ($listofvars `((mlist) ,vars1 ,vars2 ,vars3)))
2713 (if (<= ($length lvars) 2)
2714 ;; we do have a valid parametric set. Push it into
2715 ;; the functions stack, along with their domain
2716 (progn
2717 (push `(,exprn ,xrange ,yrange) functions)
2718 ;; add a title to the titles stack
2719 (push "Parametric function" titles)
2720 ;; unknown variables in the parametric equations
2721 ;; ----- GNUPLOT 4.0 WORK-AROUND -----
2722 (when (and ($constantp (fourth exprn))
2723 (getf options '$gnuplot_4_0))
2724 (setf (getf options '$const_expr)
2725 ($float (meval (fourth exprn))))))
2726 (merror
2727 (intl:gettext "plot3d: there must be at most two variables; found: ~M")
2728 lvars))))
2730 ;; expr is a simple function with its own domain. Push the
2731 ;; function and its domain into the functions stack
2732 (setq xrange (second domain))
2733 (setq yrange (third domain))
2734 (push `(,(second exprn) ,xrange ,yrange) functions)
2735 ;; push a title for this plot into the titles stack
2736 (if (< (length (ensure-string (second exprn))) 36)
2737 (push (ensure-string (second exprn)) titles)
2738 (push "Function" titles)))
2740 ;; syntax error. exprn does not have the expected form
2741 (merror
2742 (intl:gettext
2743 "plot3d: argument must be a list of three expressions; found: ~M")
2744 exprn))))
2745 (progn
2746 ;; exprn is a simple function, defined in the global domain.
2747 (if (and (getf options '$xvar) (getf options '$yvar))
2748 ;; the global domain has already been defined; use it.
2749 (progn
2750 (setq xrange `((mlist) ,(getf options '$xvar)
2751 ,(first (getf options '$x))
2752 ,(second (getf options '$x))))
2753 (setq yrange `((mlist) ,(getf options '$yvar)
2754 ,(first (getf options '$y))
2755 ,(second (getf options '$y)))))
2756 ;; the global domain should be defined by the last two lists
2757 ;; in fun. Extract it and check whether it is valid.
2758 (progn
2759 (setq
2760 domain
2761 (check-list-plot3d (append `((mlist) ,exprn) (last fun 2))))
2762 (setq fun (butlast fun 2))
2763 (if (= 3 (length domain))
2764 ;; domain is valid. Make it the global one.
2765 (progn
2766 (setq xrange (second domain))
2767 (setq yrange (third domain))
2768 (setf (getf options '$xvar) (second xrange))
2769 (setf (getf options '$x) (cddr xrange))
2770 (setf (getf options '$yvar) (second yrange))
2771 (setf (getf options '$y) (cddr yrange)))
2772 (merror usage))))
2773 ;; ----- GNUPLOT 4.0 WORK-AROUND -----
2774 (when (and ($constantp exprn) (getf options '$$gnuplot_4_0))
2775 (setf (getf options '$const_expr) ($float (meval exprn))))
2776 ;; push the function and its domain into the functions stack
2777 (push `(,exprn ,xrange ,yrange) functions)
2778 ;; push a title for this plot into the titles stack
2779 (if (< (length (ensure-string exprn)) 36)
2780 (push (ensure-string exprn) titles)
2781 (push "Function" titles))))
2782 (when (= 0 (length fun)) (return)))
2783 ;; recover the original ordering for the functions and titles stacks
2784 (setq functions (reverse functions))
2785 (setq titles (reverse titles))
2786 ;; parse the options given to plot3d
2787 (setq options (plot-options-parser extra-options options))
2788 (setq tem (getf options '$transform_xy))
2789 (when (and (member '$gnuplot_pm3d options) (null (getf options '$gnuplot_pm3d)))
2790 (setf (getf options '$palette) nil))
2791 (setq *plot-realpart* (getf options '$plot_realpart))
2792 ;; set up the labels for the axes, unless no box is being shown
2793 (unless (and (member '$box options) (not (getf options '$box)))
2794 (if (and (getf options '$xvar) (getf options '$yvar) (null tem))
2795 (progn
2796 ;; Don't set xlabel (ylabel) if the user specified one.
2797 (unless (getf options '$xlabel)
2798 (setf (getf options '$xlabel) (ensure-string (getf options '$xvar))))
2799 (unless (getf options '$ylabel)
2800 (setf (getf options '$ylabel) (ensure-string (getf options '$yvar)))))
2801 (progn
2802 (setf (getf options '$xlabel) "x")
2803 (setf (getf options '$ylabel) "y")))
2804 (unless (getf options '$zlabel) (setf (getf options '$zlabel) "z")))
2805 ;; x and y should not be bound, when an xy transformation function is used
2806 (when tem (remf options '$x) (remf options '$y))
2807 ;; Set up the plot command
2808 (let (plot (legend (getf options '$legend)))
2809 ;; titles will be a list. Titles given in the legend option prevail
2810 ;; over titles generated by plot3d. No legend if option [legend,false]
2811 (unless (listp legend) (setq legend (list legend)))
2812 (when (member '$legend options)
2813 (if (first legend) (setq titles legend)) (setq titles nil))
2814 (case (getf options '$plot_format)
2815 ($xmaxima
2816 (setq plot (make-instance 'xmaxima-plot)))
2817 ($gnuplot
2818 (setq plot (make-instance 'gnuplot-plot)))
2819 ($gnuplot_pipes
2820 (setq plot (make-instance 'gnuplot-plot))
2821 (setf (slot-value plot 'pipe) T))
2822 ($geomview
2823 (setq plot (make-instance 'geomview-plot)))
2825 (merror (intl:gettext "plot3d: plot format ~M not supported")
2826 (getf options '$plot_format))))
2827 ;; Parse plot object and pass it to the graphic program
2828 (setq output-file (plot-preamble plot options))
2829 (plot3d-command plot functions options titles)
2830 (plot-shipout plot options output-file)))
2832 ;; Given a Maxima list with 3 elements, checks whether it represents a function
2833 ;; defined in a 2-dimensional domain or a parametric representation of a
2834 ;; 3-dimensional surface, depending on two parameters.
2835 ;; The return value will be a Maxima list if the test is successful or nil
2836 ;; otherwise.
2837 ;; In the case of a function and a 2D domain, it returns the domain, validated.
2838 ;; When it is a parametric representation it returns an empty Maxima list.
2840 (defun check-list-plot3d (lis)
2841 (let (xrange yrange)
2842 ;; Makes sure list has the form ((mlist) $atom item1 item2)
2843 (unless (and ($listp lis) (= 3 ($length lis)) (not ($listp (second lis))))
2844 (return-from check-list-plot3d nil))
2845 ;; we might have a function with domain or a parametric representation
2846 (if ($listp (third lis))
2847 ;; lis is probably a function with a valid domain
2848 (if ($listp (fourth lis))
2849 ;; we do have a function and a domain. Return the domain
2850 (progn
2851 (setq xrange (check-range (third lis)))
2852 (setq yrange (check-range (fourth lis)))
2853 (return-from check-list-plot3d `((mlist) ,xrange ,yrange)))
2854 ;; wrong syntax: [expr1, list, expr2]
2855 (return-from check-list-plot3d nil))
2856 ;; lis is probably a parametric representation
2857 (if ($listp (fourth lis))
2858 ;; wrong syntax: [expr1, expr2, list]
2859 (return-from check-list-plot3d nil)
2860 ;; we do have a parametric representation. Return an empty list
2861 (return-from check-list-plot3d '((mlist)))))))