1 ;; Copyright (C) 2001, 2002, 2003, 2004 Jesper Harder
2 ;; Copyright (C) 2007, 2008 Yasuaki Honda
4 ;; Plotting support section of this file is the copy of the same
5 ;; section of wxmathml.lisp with very small modification. The file
6 ;; wxmathml.lisp is a part of the distribution of wxMaxima.
8 ;; Author: Jesper Harder <harder@ifa.au.dk>
9 ;; Created: 14 Nov 2001
12 ;; $Id: imaxima.lisp,v 1.8 2011-01-05 22:49:31 riotorto Exp $
14 ;; This program is free software; you can redistribute it and/or
15 ;; modify it under the terms of the GNU General Public License as
16 ;; published by the Free Software Foundation; either version 2 of
17 ;; the License, or (at your option) any later version.
19 ;; This program is distributed in the hope that it will be
20 ;; useful, but WITHOUT ANY WARRANTY; without even the implied
21 ;; warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
22 ;; PURPOSE. See the GNU General Public License for more details.
24 ;; You should have received a copy of the GNU General Public
25 ;; License along with this program; if not, write to the Free
26 ;; Software Foundation, Inc., 59 Temple Place, Suite 330, Boston,
30 ;;; Putting prefix package name to the variable does cause
31 ;;; error when the file is loaded into older clisp, e.g. 2.29.
32 ;;; I changed it so that it checks the existence of the symbol
33 ;;; in the custom package prior to accessing it.
34 ;;; by yasuaki honda 2006/02/26
36 ;;; When imaxima-setup bug in imaxima.el was fixed,
37 ;;; it became clear that the following code does not work
38 ;;; when imaxima.lisp is loaded by:
39 ;;; %i1 load("/xxx/imaxima.lisp");
40 ;;; Putting prefix package name to the variable solves the
45 ;;; There is a report that some Linux provides Maxima with GCL
46 ;;; which does not support handler-bind. The macro
47 ;;; style-warning-suppressor
48 ;;; is introduced to check if handler-bind is defined or not.
50 ;;; by yasuaki honda 2007/06/10
55 (setq $maxima_frontend
"imaxima")
56 (setq $maxima_frontend_version
*autoconf-version
*)
58 (defvar *windows-OS
* (string= *autoconf-windows
* "true"))
59 (defmvar $wxplot_size
'((mlist simp
) 400 250))
60 (defmvar $wxplot_old_gnuplot nil
)
61 (defvar *image-counter
* 0)
64 ;;; Following function wx-gnuplot-installed-p and the macro
65 ;;; wx-gnuplot-installation-check should be in plotting section
66 ;;; later in this file. However, because they must be in the
67 ;;; real toplevel, they are moved here.
69 (defun wx-gnuplot-installed-p ()
71 (cond ((member :linux
*features
*)
72 (let* ((tmp-stream (open "| which gnuplot" :direction
:input
))
73 (result (read-line tmp-stream nil
:eof
)))
74 (if (eql result
:eof
) nil t
)))
75 ((and (member :mingw32
*features
*)
76 (probe-file "c:\\Windows\\System32\\where.exe"))
77 (let* ((tmp-stream (open "| where wgnuplot" :direction
:input
))
78 (result (read-line tmp-stream nil
:eof
)))
79 (if (eql result
:eof
) nil t
)))
82 ;; The function check-gnuplot-process is defined in
83 ;; maxima/src/plot.lisp since at least 5.12.0.
84 (handler-case (progn (check-gnuplot-process) t
)
87 (defun wx-gnuplot-installation-check ()
88 (if (not (wx-gnuplot-installed-p))
89 (merror (format t
"Gnuplot error: Gnuplot is not installed,
90 nor Gnuplot is not recognized by maxima"))))
92 (defmacro style-warning-suppressor
(&rest body
)
93 (if (member :clisp
*features
*)
95 '(let ((scr (find-symbol "*SUPPRESS-CHECK-REDEFINITION*" :CUSTOM
)))
98 (if (macro-function 'handler-bind
)
99 `(handler-bind ((style-warning #'muffle-warning
))
103 (style-warning-suppressor
106 (special lop rop $gcprint $inchar
*autoconf-version
*)
107 (*expr tex-lbp tex-rbp
))
110 ;;; Very unfortunately, the following code does not work in
114 (unless (fboundp 'maxima
::print-invert-case
)
115 (defun print-invert-case (obj)
116 (princ-to-string obj
)))
118 (defun print-case-sensitive (obj)
120 (print-invert-case obj
)
123 (defun diff-symbol () '$d
)
125 (defun memq (elem seq
)
126 #+(or cmu scl
) (declare (inline member
))
127 (member elem seq
:test
#'eq
))
129 (defun main-prompt ()
130 (format () (concatenate 'string
(string (code-char 3)) "(~A~D) " (string (code-char 4)))
131 (stripdollar (print-case-sensitive $inchar
)) $linenum
))
133 (defun break-dbm-loop (at)
135 (*quit-tags
* (cons (cons *break-level
* *quit-tag
*) *quit-tags
*))
136 (*break-level
* (if (not at
) *break-level
* (cons t
*break-level
*)))
137 (*quit-tag
* (cons nil nil
))
138 (*break-env
* *break-env
*)
140 (*diff-bindlist
* nil
)
141 (*diff-mspeclist
* nil
)
144 (declare (special *mread-prompt
* ))
145 (and (consp at
) (set-env at
))
147 (break-frame 0 nil
)))
148 (catch 'step-continue
154 (string (code-char 3))
156 (string (code-char 4)))
157 (unless (stringp at
) "dbm")
158 (length *quit-tags
*))
161 (let ((res (dbm-read *debug-io
* nil
*top-eof
* t
)))
162 (declare (special *mread-prompt
*))
163 (cond ((and (consp res
) (keywordp (car res
)))
164 (let ((value (break-call (car res
)
165 (cdr res
) 'break-command
)))
166 (cond ((eq value
:resume
) (return)))
169 (setq $__
(nth 2 res
))
170 (setq $%
(meval* $__
))
182 (setq $display2d
'$imaxima
)
185 ;; (c) copyright 1987, Richard J. Fateman
186 ;; Small changes for interfacing with TeXmacs: Andrey Grozin, 2001
187 ;; Yet more small changes for interfacing with imaxima: Jesper Harder 2001
189 ;; (defun tex (... is removed
191 (defun unquote-%-internal
(str c
)
192 (let* ((qstr (format nil
"~A~A" #\\ c
))
193 (pos (search qstr str
)))
195 (concatenate 'string
(subseq str
0 pos
) (format nil
"~A" c
)
196 (unquote-%-internal
(subseq str
(+ pos
2)) c
))
199 (defun unquote-%
(str)
200 (setq str
(unquote-%-internal str
#\$
))
201 (setq str
(unquote-%-internal str
#\%
))
202 (setq str
(unquote-%-internal str
#\
&))
203 (setq str
(unquote-%-internal str
#\_
))
204 (setq str
(unquote-%-internal str
#\
#))
207 (defun tex-string (x)
210 (print-case-sensitive x
)
212 (cond ((equal sym-name
"") "")
213 ((eql (elt sym-name
0) #\\) sym-name
)
214 ((memq (elt sym-name
0) '(#\$
#\
&))
215 (setq sym-name
(unquote-%
(subseq sym-name
1)))
216 (concatenate 'string
"\\verb| " (verb-quote sym-name
) "|"))
217 (t (setq sym-name
(unquote-% sym-name
))
218 (concatenate 'string
"\\verb|" (verb-quote sym-name
) "|")))))
220 (defun verb-quote (str)
221 (let ((var "") (charlist
222 '((#\Newline .
"| \\\\ \\verb| "))))
223 (dotimes (i (length str
))
224 (let ((chari (elt str i
)))
225 (setq var
(concatenate 'string var
226 (or (cdr (assoc chari charlist
:test
#'eql
))
232 (if (eql x
#\|
) "\\verb/|/"
233 (concatenate 'string
"\\verb|" (string x
) "|")))
236 (let ((var "") (charlist
237 '((#\
{ .
"\\left\\{\\right.")
238 (#\
} .
"\\left\\}\\right.")
240 (#\Newline .
"} \\\\ \\mathrm{ ")
246 (dotimes (i (length str
))
247 (let ((chari (elt str i
)))
248 (setq var
(concatenate 'string var
249 (or (cdr (assoc chari charlist
:test
#'eql
))
253 (defun tex-stripdollar (sym)
254 (or (symbolp sym
) (return-from tex-stripdollar sym
))
255 (let* ((name (print-case-sensitive sym
))
256 (pname (if (memq (elt name
0) '(#\$
#\
&)) (subseq name
1) name
))
259 ((eql l
1) (myquote pname
))
260 (t (concatenate 'string
"\\mathrm{" (myquote pname
) "}")))))
262 ;; (defun strcat (... is removed
264 ;; 10/14/87 RJF convert 1.2e20 to 1.2 \cdot 10^{20}
265 ;; 03/30/01 RLT make that 1.2 \times 10^{20}
266 ;; (defun texnumformat(atom) is removed
268 ;; (defun tex-paren (x l r) is removed
271 ;;; The definition of tex-array is modified to fix bug #30, reported by Thomas Weidner.
272 ;;; The following definition is provided by Thomas.
276 (defun tex-array (x l r
)
278 (if (eq 'mqapply
(caar x
))
282 (if (and (atom (cadr x
)) (atom f
))
283 ;; subscript is an atom -- don't use \isubscript
285 (setq l
(tex f l nil lop
'mfunction
)
286 r
(nconc (tex-list (cdr x
) nil
(list "}") ",") r
))
287 (nconc l
(list "_{") r
))
289 (setq l
(tex f
(append l
(list "\\isubscript{")) nil lop
'mfunction
)
290 r
(nconc (tex-list (cdr x
) nil
(list "}") ",") r
))
291 (nconc l
(list "}{") r
)))))
293 ;; set up a list , separated by symbols (, * ...) and then tack on the
294 ;; ending item (e.g. "]" or perhaps ")"
296 (defun tex-list (x l r sym
)
300 (setq nl
(nconc nl
(tex (car x
) l r
'mparen
'mparen
)))
302 ;; (setq nl (nconc nl (tex (car x) l (list sym) 'mparen 'mparen))
303 (setq nl
(nconc nl
(tex (car x
) l
(list (concatenate 'string sym
"\\linebreak[0]")) 'mparen
'mparen
))
307 ;; (defun tex-prefix (x l r) is removed
309 ;; (defun tex-infix (x l r) is removed
311 ;; (defun tex-postfix (x l r) is removed
313 ;; (defun tex-nary (x l r) is removed
315 (defun tex-nary (x l r
)
316 (let* ((op (caar x
)) (sym (texsym op
)) (y (cdr x
)) (ext-lop lop
) (ext-rop rop
))
317 (cond ((null y
) (tex-function x l r t
)) ; this should not happen
318 ((null (cdr y
)) (tex-function x l r t
)) ; this should not happen, too
319 (t (do ((nl) (lop ext-lop op
) (rop op
(if (null (cdr y
)) ext-rop op
)))
320 ((null (cdr y
)) (setq nl
(nconc nl
(tex (car y
) l r lop rop
))) nl
)
321 (setq nl
(nconc nl
(tex (car y
) l
(list sym
) lop rop
))
325 ;; (defun tex-nofix (x l r) is removed
327 ;; (defun tex-matchfix (x l r) is removed
329 ;; (defun texsym (x) is removed
331 ;; (defun texword (x) is removed
333 ;; (defprop bigfloat tex-bigfloat tex) is removed
336 ;;; Fixed to treat big float correctly.
338 (defun tex-bigfloat (x l r
) (tex-list (fpformat x
) l r nil
))
341 (defprop $%phi
"\\phi" texword
) ;; yhonda
343 ;; reported conjugate treatment in imaxima be fixed.
344 (defprop $conjugate
("^{\\star}") texsym
)
346 (defprop mquote
201. tex-rbp
)
348 (defprop msetq
180. tex-rbp
)
349 (defprop msetq
20. tex-rbp
)
351 (defprop mset
180. tex-lbp
)
352 (defprop mset
20. tex-rbp
)
354 (defprop mdefine
180. tex-lbp
)
355 (defprop mdefine
20. tex-rbp
)
357 (defprop mdefmacro
180. tex-lbp
)
358 (defprop mdefmacro
20. tex-rbp
)
360 (defprop marrow
25 tex-lbp
)
361 (defprop marrow
25 tex-rbp
)
363 (defprop mfactorial
160. tex-lbp
)
365 (defprop mexpt
140. tex-lbp
)
366 (defprop mexpt
139. tex-rbp
)
369 (defprop mncexpt
135. tex-lbp
)
370 (defprop mncexpt
134. tex-rbp
)
372 (defprop mnctimes
110. tex-lbp
)
373 (defprop mnctimes
109. tex-rbp
)
375 ;;(defprop mtimes tex-nary tex)
376 ;;(defprop mtimes "\\*" texsym)
377 (defprop mtimes
120. tex-lbp
)
378 (defprop mtimes
120. tex-rbp
)
380 (defprop %sqrt tex-sqrt tex
)
382 (defun tex-sqrt(x l r
)
383 ;; format as \\sqrt { } assuming implicit parens for sqr grouping
384 (tex (cadr x
) (append l
'("\\isqrt{")) (append '("}") r
) 'mparen
'mparen
))
386 (defprop mquotient
122. tex-lbp
) ;;dunno about this
387 (defprop mquotient
123. tex-rbp
)
389 (defun tex-mquotient (x l r
)
390 (if (or (null (cddr x
)) (cdddr x
)) (wna-err (caar x
)))
391 (cond ((and (atom (cadr x
)) (atom (caddr x
)))
392 ;; both denom and numerator are atoms
393 (setq l
(tex (cadr x
) (append l
'("\\frac{")) nil nil nil
) ;;fixme
394 r
(tex (caddr x
) (list "}{") (append '("}")r
) 'mparen
'mparen
)))
396 ;; numerator is an atom
397 (setq l
(tex (cadr x
) (append l
'("\\ifracd{")) nil
'mparen
'mparen
)
398 r
(tex (caddr x
) (list "}{") (append '("}")r
) 'mparen
'mparen
)))
401 (setq l
(tex (cadr x
) (append l
'("\\ifracn{")) nil
'mparen
'mparen
)
402 r
(tex (caddr x
) (list "}{") (append '("}")r
) 'mparen
'mparen
)))
405 (setq l
(tex (cadr x
) (append l
'("\\ifrac{")) nil
'mparen
'mparen
)
406 r
(tex (caddr x
) (list "}{") (append '("}")r
) 'mparen
'mparen
))))
409 ;; easily extended to union, intersect, otherops
411 ;; (defun tex-limit(x l r) is removed. mactex.lisp version considers direction.
413 ;;binomial coefficients
415 (defprop %binomial tex-choose tex
)
417 ;; (defun tex-choose (x l r) is removed
419 (defprop rat
120. tex-lbp
)
420 (defprop rat
121. tex-rbp
)
422 (defprop mplus
100. tex-lbp
)
423 (defprop mplus
100. tex-rbp
)
425 ;; (defun tex-mplus (x l r) is removed
427 (defprop mminus
100. tex-rbp
)
428 (defprop mminus
100. tex-lbp
)
430 (defprop mequal
80. tex-lbp
)
431 (defprop mequal
80. tex-rbp
)
433 (defprop mnotequal
80. tex-lbp
)
434 (defprop mnotequal
80. tex-rbp
)
436 (defprop mgreaterp
80. tex-lbp
)
437 (defprop mgreaterp
80. tex-rbp
)
439 (defprop mgeqp
80. tex-lbp
)
440 (defprop mgeqp
80. tex-rbp
)
442 (defprop mlessp
80. tex-lbp
)
443 (defprop mlessp
80. tex-rbp
)
445 (defprop mleqp
80. tex-lbp
)
446 (defprop mleqp
80. tex-rbp
)
448 (defprop mnot
70. tex-rbp
)
450 (defprop mand
80. tex-lbp
)
451 (defprop mand
80. tex-rbp
)
453 (defprop mor
50. tex-lbp
)
454 (defprop mor
50. tex-rbp
)
456 ;; make sin(x) display as sin x , but sin(x+y) as sin(x+y)
461 (%acot
"\\operatorname{arccot}")
462 (%asec
"\\operatorname{arcsec}")
463 (%acsc
"\\operatorname{arccsc}")
464 (%sech
"\\operatorname{sech}")
465 (%csch
"\\operatorname{csch}")
466 (%asinh
"\\operatorname{arcsinh}")
467 (%acosh
"\\operatorname{arccosh}")
468 (%atanh
"\\operatorname{arctanh}")
469 (%acoth
"\\operatorname{arccoth}")
470 (%asech
"\\operatorname{arcsech}")
471 (%acsch
"\\operatorname{arccsch}")
474 (defprop mcond
25. tex-lbp
)
475 (defprop mcond
25. tex-rbp
)
476 (defprop %derivative tex-derivative tex
)
478 (defprop mdo
30. tex-lbp
)
479 (defprop mdo
30. tex-rbp
)
480 (defprop mdoin
30. tex-rbp
)
482 ;; these aren't quite right
485 ;; Undone and trickier:
486 ;; handle reserved symbols stuff, just in case someone
487 ;; has a macsyma variable named (yuck!!) \over or has a name with
489 ;; Maybe do some special hacking for standard notations for
490 ;; hypergeometric fns, alternative summation notations 0<=n<=inf, etc.
492 ;;Undone and really pretty hard: line breaking
495 (defun tex-mtext (x l r
) (tex-list (cdr x
) l r
""))
497 (defun tex-mlabel (x l r
)
501 (list (format nil
(concatenate 'string
(string (code-char 23))
503 (string (code-char 23)))
504 (myquote (print-case-sensitive (stripdollar (cadr x
))))))
508 (defun tex-spaceout (x l r
)
509 (append l
(list "\\verb|" (make-string (cadr x
) :initial-element
#\space
) "|") r
))
514 ; (princ x) ;; uncomment to debug.
515 (if (and (listp x
) (car x
) (listp (car x
)) (caar x
)
516 (equal (caar x
) 'mlabel
)
519 (input-label-p (cadr x
)))
520 (let (($display2d nil
))
521 (declare (special $display2d
))
523 (return-from latex
)))
526 (if (and (listp x
) (cdr x
) (stringp (cadr x
))
527 (equal (string-right-trim '(#\Space
) (cadr x
)) "Is"))
528 (tex x
(list (string (code-char 21)))
529 (list (string (code-char 22))) 'mparen
'mparen
)
530 (tex x
(list (string (code-char 2)))
531 (list (string (code-char 5))) 'mparen
'mparen
))))
533 (defun input-label-p (label)
535 (let ((name (symbol-name label
)))
536 (and (> (length name
) 3)
537 (string= "$%I" (subseq name
0 3))))))
539 (let ((old-displa (symbol-function 'displa
)))
541 (if (eq $display2d
'$imaxima
)
543 (funcall old-displa form
))))
545 (defun ask-prop (object property fun-or-number
)
546 (if fun-or-number
(setq fun-or-number
(list '| | fun-or-number
)))
547 ;;; Asks the user a question about the property of an object.
548 ;;; Returns only $yes, $no or $unknown.
549 (if (symbolp property
)
550 (setq property
(print-case-sensitive property
)))
551 (do ((end-flag) (answer))
552 (end-flag (cond ((memq answer
'($yes |$Y| |$y|
)) '$yes
)
553 ((memq answer
'($no |$N| |$n|
)) '$no
)
554 ((memq answer
'($unknown $uk
)) '$unknown
)))
555 (setq answer
(retrieve
556 `((mtext) "Is " ,object
557 ,(if (member (get-first-char property
) '(#\a #\e
#\i
#\o
#\u
)
561 ,property
,@fun-or-number
"?")
564 ((memq answer
'($yes |$Y| |$y| |$N| |$n| $no $unknown $uk
))
567 "~%Acceptable answers are Yes, Y, No, N, Unknown, Uk~%")))))
573 (defun wxxml-tag (x l r
)
574 (let ((name (cadr x
))
576 (append l
(list (format nil
"<~a>~a</~a>" tag name tag
)) r
)))
579 (defun wxplot-filename (&optional
(suff t
) &aux filename
)
580 (incf *image-counter
*)
582 (plot-temp-file (if suff
583 (format nil
"maxout_~d.eps" *image-counter
*)
584 (format nil
"maxout_~d" *image-counter
*))))
585 (if (probe-file filename
)
586 (delete-file filename
))
589 (defun $wxplot_preamble
()
590 (let ((frmt (if $wxplot_old_gnuplot
591 "set terminal postscript picsize ~d ~d; set zeroaxis;"
592 "set terminal postscript size ~d,~d; set zeroaxis;")))
594 ($first $wxplot_size
)
595 ($second $wxplot_size
))))
599 (mfuncall '$makelist x x i j
)))
601 (defun $wxplot2d
(&rest args
)
602 ;; if gnuplot is not installed, this will terminate the
603 ;; further execution.
604 (wx-gnuplot-installation-check)
605 (let ((preamble ($wxplot_preamble
))
606 (system-preamble (get-plot-option-string '$gnuplot_preamble
2))
607 (filename (wxplot-filename)))
608 (if (length system-preamble
)
609 (setq preamble
(format nil
"~a; ~a" preamble system-preamble
)))
611 (if (and (listp arg
) (eql (cadr arg
) '$gnuplot_preamble
))
612 (setq preamble
(format nil
"~a; ~a"
613 preamble
(caddr arg
)))))
614 (apply #'$plot2d
`(,@args
615 ((mlist simp
) $plot_format $gnuplot
)
616 ;; ((mlist simp) $gnuplot_preamble ,preamble)
617 ((mlist simp
) $gnuplot_term $ps
)
618 ((mlist simp
) $gnuplot_out_file
,filename
)))
619 ($ldisp
`((wxxmltag simp
) ,filename
"img")))
622 (defun $wxplot3d
(&rest args
)
623 ;; if gnuplot is not installed, this will terminate the
624 ;; further execution.
625 (wx-gnuplot-installation-check)
626 (let ((preamble ($wxplot_preamble
))
627 (system-preamble (get-plot-option-string '$gnuplot_preamble
2))
628 (filename (wxplot-filename)))
629 (if (length system-preamble
)
630 (setq preamble
(format nil
"~a; ~a" preamble system-preamble
)))
632 (if (and (listp arg
) (eql (cadr arg
) '$gnuplot_preamble
))
633 (setq preamble
(format nil
"~a; ~a"
634 preamble
(caddr arg
)))))
635 (apply #'$plot3d
`(,@args
636 ((mlist simp
) $plot_format $gnuplot
)
637 ;; ((mlist simp) $gnuplot_preamble ,preamble)
638 ((mlist simp
) $gnuplot_term $ps
)
639 ((mlist simp
) $gnuplot_out_file
,filename
)))
640 ($ldisp
`((wxxmltag simp
) ,filename
"img")))
643 (defun $wxdraw2d
(&rest args
)
645 (list (cons '($gr2d
) args
))))
648 (defun $wxdraw3d
(&rest args
)
650 (list (cons '($gr3d
) args
))))
652 (defun $wxdraw
(&rest args
)
653 ;; if gnuplot is not installed, this will terminate the
654 ;; further execution.
655 (wx-gnuplot-installation-check)
656 (let* ((filename (wxplot-filename nil
))
659 (if (not (fboundp '$draw
))
661 ;; Usually the following is used.
662 ;; (setq res (apply #'$draw
663 ;; However, CMUCL warns that function $draw is not defined.
664 ;; To suppress this warning, symbol-function is used to make
665 ;; clear that the runtime definition is used rather than
667 (setq res
(apply (symbol-function '$draw
)
670 ((mequal simp
) $terminal $eps_color
)
671 ((mequal simp
) $dimensions
673 ;; convert points to 1/100 of cm
674 ,(* 3.53 ($first $wxplot_size
))
675 ,(* 3.53 ($second $wxplot_size
))))
676 ((mequal simp
) $file_name
,filename
))
678 ($ldisp
`((wxxmltag simp
) ,(format nil
"~a.eps" filename
) "img"))
681 (defun $wximplicit_plot
(&rest args
)
682 ;; if gnuplot is not installed, this will terminate the
683 ;; further execution.
684 (wx-gnuplot-installation-check)
685 (let ((preamble ($wxplot_preamble
))
686 (system-preamble (get-plot-option-string '$gnuplot_preamble
2))
687 (filename (wxplot-filename)))
688 (if (not (fboundp '$implicit_plot
))
689 ($load
'$implicit_plot
))
690 (if (length system-preamble
)
691 (setq preamble
(format nil
"~a; ~a" preamble system-preamble
)))
693 (if (and (listp arg
) (eql (cadr arg
) '$gnuplot_preamble
))
694 (setq preamble
(format nil
"~a; ~a"
695 preamble
(caddr arg
)))))
696 (apply (symbol-function '$implicit_plot
)
698 ((mlist simp
) $plot_format $gnuplot
)
699 ;; ((mlist simp) $gnuplot_preamble ,preamble)
700 ((mlist simp
) $gnuplot_term $ps
)
701 ((mlist simp
) $gnuplot_out_file
,filename
)))
702 ($ldisp
`((wxxmltag simp
) ,filename
"img")))
706 (defun $wxcontour_plot
(&rest args
)
707 ;; if gnuplot is not installed, this will terminate the
708 ;; further execution.
709 (wx-gnuplot-installation-check)
710 (let ((preamble ($wxplot_preamble
))
711 (system-preamble (get-plot-option-string '$gnuplot_preamble
2))
712 (filename (wxplot-filename)))
713 (if (length system-preamble
)
714 (setq preamble
(format nil
"~a; ~a" preamble system-preamble
)))
716 (if (and (listp arg
) (eql (cadr arg
) '$gnuplot_preamble
))
717 (setq preamble
(format nil
"~a; ~a" preamble
(caddr arg
)))))
718 (apply #'$contour_plot
`(,@args
719 ((mlist simp
) $plot_format $gnuplot
)
720 ;; ((mlist simp) $gnuplot_preamble ,preamble)
721 ((mlist simp
) $gnuplot_term $ps
)
722 ((mlist simp
) $gnuplot_out_file
,filename
)))
724 ($ldisp
`((wxxmltag simp
) ,filename
"img")))
727 ) ;; This paran closes style-warning-suppressor.