MathGroup Archive 1990

[Date Index] [Thread Index] [Author Index]

Search the Archive

Math mode for GNU Emacs

  • To: uiucuxc!yoda.ncsa.uiuc.edu!mathgroup
  • Subject: Math mode for GNU Emacs
  • From: uiucuxc!cello.hpl.hp.com!jacobson
  • Date: Tue, 17 Apr 90 10:59:20 PDT

Here is a GNU Emacs package for use with Mathematica.  
Its main features are:  

  * Editing of multi-line "cells" before submission.
  * Limited error checking before submission
  * Copying of earlier cells by name or by pointing.
  * Go to the point of an error in a .m file.
  * On-line help
  * Symbol completion
  * Interrupts

Installation: Copy the stuff below the ======== line below to math.el
in whatever directory you put emacs-lisp stuff in.  (If you don't
know, type go to the *scratch* buffer, type load-path C-u C-x C-e.  If
none of those directories are writable by you, ask an emacs expert to
make you directory for your own private emacs stuff.)  

Check the $Path variable of your version of Mathematica.  Edit the
Mathematica-search-path variable, which is set in the 3rd line beyond
the legalese (or just make make sure it is set before loading this) to
match.  Use nil for the current working directory.  Also make sure
that the emacs variable math-process-string (just below
Mathematica-search-path) reflects the location of Mathematica on your
system.  

When you want to use math-mode, first type M-x load-library RET math RET

After loading, type M-x math to start a copy of Mathematica.  Edit an
input cell using normal editing commands, the submit with ESC-RET.

If Mathematica detects a syntax error, it will be indicated with
"^--error".  Fix the error, cut out the "^--error", and resubmit.  

You can complete Mathematica symbols, in both the working buffer and
in other math-mode buffers,  with ESC-TAB.  Do not try this when Mathematica 
is busy or chaos will result.

You can get help on Mathematica symbols, in both the working buffer
and in other math-mode buffers, with C-h e or C-h E (the latter is
more verbose).  Again, don't try this when Mathematica is busy.  HP
users, please note that C-h and DEL are usually reversed in most GNU
Emacs installations.

You can copy cells to the end of the buffer with C-c C-y.  It will ask
for what cell you want in the minibuffer.

  <nn> 		copies cell number <nn>
  <empty> 	copies the previous In cell if the cursor is after the
		last In[..], otherwise copies the cell the cursor is in.
		This latter case will copy an In cell, an Out cell containing
		no blank lines (especially useful with InputForm), or 
		just any block of text.  This also works from any math-mode 
		buffer, but copies to the math process buffer (one
		with an active Mathematica process--normally *math*, but 
		it be changed with set-math-process-buffer).

With a prefix arg, the <nn> option will back over incarnation
boundaries of Mathematica.  See the on-line help for math-copy-cell
for more info.

C-c C-c interrupts Mathematica (as well is it can be interrupted).
When it gives you the prompt, type your response followed by ESC-RET.

C-c 9 is equivalent to kill -9 <Mathematica process number>.

If you have read in a .m file with "<<", and have gotten 
a response of the form

	"<filename>: <lineno>: syntax error in ..."

you can go directly to the point of the error by typing C-c C-e.
This is very useful because the line numbers are almost always wrong.
This function counts lines the way Mathematica does.  (There are reports
of this not working with older versions of Emacs.)

C-h e, C-h E, (help commands), and ESC-TAB (math-complete-symbol)
depend on a running Mathematica process.  C-c C-y affects a buffer
expected to have a running Mathematica process.  These commands can
all be used from a buffer that does not have a running Mathematica
process, in which case they affect a buffer that does.  The default is
*math*, the buffer created by the math command, but the buffer can be
changed with M-x set-math-process-buffer.  Different buffers can have
different associated math process buffers.

Bugs/limitations: 
If the input is does not form a complete statement, Mathematica
may hang waiting for more input.  If this happens, type a RET to add a
blank line, then ESC-RET to send an empty cell, which will clear
Mathematica's input buffer.  Cut away the new prompt, fix the cell and
resubmit.  Do not just fix the input and hit ESC-RET, as Mathematica
will get the concatenation of both the first submission and the second.  
(You can demonstrate incomplete statements on the input "5+".)

If you change Mathematica's $Path variable, C-c C-e may be unable to
find the file (or may find the wrong file).  A solution short of
changing the Mathematica-search-path variable (using M-x set-variable)
is to visit the file, then use M-x goto-matherr-line.

The code that locates errors after typing ESC-RET depends on certain
output being delevered from the process in complete chunks.  Emacs
documentation explicitly forbids relying on this property.  Therefore
this feature may be unreliable or non-portable.

Fancy installation:

You can avoid having to explicitly load the math package by putting
the following lines in your .emacs file

(autoload 'math "math" "Starts Mathematica in a separate buffer" t)
(autoload 'math-mode  "math" "A mode for running Mathematica or
editing Mathematica source files." t)
(autoload 'start-math "math" "Starts Mathematica in the current
buffer" t)
(setq auto-mode-alist (cons '("\\.m$" . math-mode) auto-mode-alist))

Math-mode will run faster if you "byte-compile" it.  Type M-x
byte-compile-file math.el (make sure the directory is right).  

Enjoy,
  -- David Jacobson
================================
;; math.el, a mode package for Mathematica.  
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;; Copyright (c) 1990 Hewlett-Packard Company, all rights reserved.
;; 
;;                             LEGAL NOTICE
;; 
;; This math-mode package is experimental and HP shall have no obligation to
;; maintain or support it.  HP makes no express or implied warranty of any
;; kind with respect to this software, and HP shall not be liable for any
;; direct, indirect, special, incidental or consequential damages (whether
;; based on contract, tort or any other legal theory) arising in any way from
;; use of the software.
;; 
;; Everyone is granted permission to copy, modify and redistribute this
;; math-mode package, provided:
;;  1.  All copies contain this copyright notice.
;;  2.  All modified copies shall carry a prominant notice stating who
;;      made the last modification and the date of such modification.
;;  3.  No charge is made for this software or works derived from it.  
;;      This clause shall not be construed as constraining other software
;;      distributed on the same medium as this software, nor is a
;;      distribution fee considered a charge.
;;
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;; Portions of this package were adapted from GNU Emacs.
;;
;; Copyright (C) 1985, 1986, 1987, 1988 Free Software Foundation, Inc. 
;; 
;; GNU Emacs is distributed in the hope that it will be useful,
;; but WITHOUT ANY WARRANTY.  No author or distributor
;; accepts responsibility to anyone for the consequences of using it
;; or for whether it serves any particular purpose or works at all,
;; unless he says so in writing.  Refer to the GNU Emacs General Public
;; License for full details.

;; Everyone is granted permission to copy, modify and redistribute
;; GNU Emacs, but only under the conditions described in the
;; GNU Emacs General Public License.   A copy of this license is
;; supposed to have been given to you along with GNU Emacs so you
;; can know your rights and responsibilities.  It should be in a
;; file named COPYING.  Among other things, the copyright notice
;; and this notice must be preserved on all copies.
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;	Author: David Jacobson, jacobson at hplabs.hp.com
;;      Experimental version of April 10, 1990
;;      Assumes GNU Emacs version 18.54
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
(require 'shell)

(defvar Mathematica-search-path 
  (list nil (getenv "HOME") "/usr/local/math/Init" "/usr/local/math/Packages")
  "*A list of directories in which to look for files.  
Use nil for the current directory.")

(defconst math-process-string "/usr/local/bin/math"
  "A string to pass to the unix exec function to start Mathematica")

(defvar math-process-buffer 
  "*math*"
  "The buffer normally running Mathematica.  Certain commands
(e.g. math-complete-symbol) will go to this buffer to find a Mathematica 
process.  This can be locally set with set-math-process-buffer.")

(defconst math-header-re (concat "^" (regexp-quote "by S. Wolfram, D. Grayson, R. Maeder, H. Cejtin,"))
  "A regexp that will match somewhere in the Mathematica preamble")
						   

(defvar math-mode-map nil) 

;;; deep-copy-keymap was written by Daniel LaLiberte.
;;; Some GNU Emacs systems already have this installed.  If so
;;; comment out this function definition.

(defun deep-copy-keymap (keymap)
  "Return a deep copy of KEYMAP.  That is, all levels are copied,
not just the top level."
  (if (not (keymapp keymap))
      keymap
    (cond

     ((listp keymap)
      (let ((new-keymap (copy-alist keymap)))
	(setq keymap (cdr new-keymap))
	(while keymap
	  (let ((binding (car keymap)))
	    (if (keymapp (cdr binding))
		(setcdr binding (deep-copy-keymap (cdr binding))))
	    )
	  (setq keymap (cdr keymap))
	  )
	new-keymap
	))

      ((vectorp keymap)
       (let ((i 0)
	     (n (length keymap))
	     (new-keymap (copy-sequence keymap)))
	 (while (< i n)
	   (if (keymapp (aref keymap i))
	       (aset new-keymap i (deep-copy-keymap (aref keymap i))))
	   (setq i (1+ i)))
	 new-keymap
	 )))))


(if math-mode-map
    nil
  (setq math-mode-map (deep-copy-keymap shell-mode-map))
  (define-key math-mode-map "\C-m" 'newline) ; the global keymap maps to newline
  (define-key math-mode-map "\e\C-m" 'math-send-input)
  ;; \C-c\C-c is set to interrupt-shell-subjob in the shell-mode-mode
  ;; The name is deceptive; it sends a SIGINT signal (control C) to 
  ;; whatever process is running in the current buffer
  (define-key math-mode-map "\C-c9" 'kill-9-process)
  (define-key math-mode-map "\C-c\C-h"   'math-help); buffer specific C-h
  (define-key math-mode-map "\C-he" 'math-help) ; e-xpression in help menu
  (define-key math-mode-map "\C-hE" 'math-extra-help) ; E-xpression in help menu
  (define-key math-mode-map "\e\t"   'math-complete-symbol)
  (define-key math-mode-map "\C-c\C-y" 'math-copy-cell)
  (define-key math-mode-map "\C-c\C-e" 'find-math-error)
  (define-key math-mode-map "\C-c\C-r" 'math-isearch-backward))

(defvar math-mode-syntax-table nil
  "Syntax table used while in math mode.")

(if math-mode-syntax-table
    ()
  (setq math-mode-syntax-table (make-syntax-table))
  (modify-syntax-entry ?% "." math-mode-syntax-table)
  (modify-syntax-entry ?& "." math-mode-syntax-table)
  (modify-syntax-entry ?* ". 23" math-mode-syntax-table) ;allow for (* comment *)
  (modify-syntax-entry ?+ "." math-mode-syntax-table)
  (modify-syntax-entry ?- "." math-mode-syntax-table)
  (modify-syntax-entry ?/ "." math-mode-syntax-table)
  (modify-syntax-entry ?< "." math-mode-syntax-table)
  (modify-syntax-entry ?= "." math-mode-syntax-table)
  (modify-syntax-entry ?> "." math-mode-syntax-table)
  (modify-syntax-entry ?_ "." math-mode-syntax-table)
  (modify-syntax-entry ?\| "." math-mode-syntax-table)
  (modify-syntax-entry ?\` "_" math-mode-syntax-table) ; Mathematica context symbol
  (modify-syntax-entry ?\( "()1" math-mode-syntax-table) ;allow for (* comment *)
  (modify-syntax-entry ?\) ")(4" math-mode-syntax-table)) ;allow for (* comment *)

;;; math-send-input sends a chunk of text to Mathematica.  It
;;; interacts tightly with math-send-filter using the buffer-specific
;;; variable math-send-state and synchronizes though sending output
;;; and the accept-process-output (but see below) command.  

;;; The Emacs documentation
;;; claims that one cannot be sure how much output will be delivered
;;; in a chunk to the output filter.  However we depend on chunks of
;;; up to one line after which Mathematica immediately does a read,
;;; arriving in a single chunk.  A slightly more robust technique than
;;; doing string-match on the input string would be to put the input 
;;; into the buffer and match there.  

;;; If the Mathematica process does not send a prompt at all, the
;;; accept-process-output hangs and the only solution is to kill the
;;; mathexe process or Emacs.  This can happen if you use an Input[""]
;;; (a rather perverse thing to do).  An alternative is to replace
;;; (accept-process-output process) with (sleep-for 10).  It appears that
;;; arrival of any output causes Emacs to pop immediately out of a
;;; sleep-for.  But this could mess up if you have more than one active
;;; process running at a time or if you strke a key.  
;;; Of course, we could use a while loop and have the filter set 
;;; math-send-state to another value when it has actually gotten 
;;; something.  I tried this but ran into unknown trouble and have 
;;; not followed up on it.

;;; The variable math-send-state has the following interpretatons:
;;; non-last-line             We are in the middle of sending a
;;;                           multi-line input.  Watch for
;;;                           errors and output other than indent
;;;                           cookies.
;;;
;;; last-line                 The last line has been sent, still watch
;;;                           for syntax error messages.  Also insert
;;;                           a blank like (and warn about it) if the
;;;                           output contained any non-whitespace
;;;                           characters before a newline.
;;;               
;;; throw-away-prompt         A syntax error has been detected and a 
;;;                           newline sent to Mathematica to flush its
;;;                           input buffer.  Normally it will come
;;;                           back with a new prompt.  If the next
;;;                           input looks like a prompt, throw it
;;;                           away and give a syntax error message.
;;;                           Otherwise display that discarded
;;;                           material as a warning.
;;;
;;; normal                    Just post the output.  Actually I think
;;;                           everything that sets the mode to normal
;;;                           also sets the filter to nil, so this is
;;;                           hardly used.  (But see the exit clause of 
;;;                           the unwind-protect.)


(defun math-send-input ()
  "Send input to Mathematica.
At end of buffer, sends last \"cell\" to Mathematica.  When not at end, 
copies current \"cell\" to the end of the buffer and sends it.  Also
sends input for interrupt and Input[].  Warning: A multi-line input
to Input[\"\"] will cause deadlock."
  (interactive "*")
  (let ((process (or (get-buffer-process (current-buffer))
		     (error "Current buffer has no process")))
	bpt2
	ept2
	begpkt
	endpkt
	copy
	)
    ;; Find beginning of "cell"
    (let* ((cellinfo (math-identify-cell (point) (process-mark process)))
	   (bpt (car cellinfo))
	   (ept (nth 1 cellinfo))
	   )
      (check-math-syntax bpt ept)
      (goto-char ept)
      ;; Move to line beyond cell, adding newline if necessary.
      (forward-line 1)
      (if (or (not (bolp)) 
	      (= (point) bpt)) ; make null cells contain a newline
	  (newline))
      (setq copy (buffer-substring bpt (point)))
      ;; If we are \"near\" the end of the buffer, we don't copy the data down
      ;; there, but we kill excess white space.  Otherwise, we go there and 
      ;; copy the data.
      (if (looking-at "\\s *\\'")
	  (progn
	    (replace-match "")
	    (setq bpt2 bpt)
	    (setq ept2 (point)))
	(goto-char (point-max))
	(forward-line 0)
	(if (or (eolp) (looking-at "^In\\[[0-9]+\\]:=\\s *$"))
	    (end-of-line)
	  (end-of-line)
	  (newline))
	(setq bpt2 (point))
	(insert copy)
	(setq ept2 (point)))
      (goto-char bpt2)
      ;; indentstring is a global variable
      ;; indentstring is a the string Mathematica would have indented
      ;; the user's start point by if we were talking to it directly.
      (setq math-indent-string "")
      (set-process-filter process 'math-send-filter)
      ;; math-send-state is a global variable
      (setq math-send-state 'non-last-line)
      (setq begpkt bpt2) ; point
      (message "*")
      (unwind-protect
	  (while (eq math-send-state 'non-last-line)
	    (goto-char begpkt)
	    (forward-line 1)
	    (setq endpkt (point))
	    (if (= endpkt ept2) (setq math-send-state 'last-line))
	    (metered-process-send-string 
	     process (buffer-substring begpkt endpkt))
	    (if (eq math-send-state 'non-last-line)
		;; See discussion above.  
		(accept-process-output process)
		;;(sleep-for 10)
	      )
	    (cond ((eq math-send-state 'premature-output)
		   (setq math-send-state 'normal) ; for sake of unwind protect
		   (set-process-filter process nil)
		   (error "Unexpected output; part of cell discarded"))
		  )
	    (setq begpkt endpkt) ; advance to next line
	    ) ; end while
	;; unwind protect tail
	(if (memq math-send-state '(last-line normal))
	    ()
	  (set-process-filter process nil))))))

      

(defun math-send-filter (proc string)
  (let ((cbuf (current-buffer))
	(save-match-data (match-data)))
    (unwind-protect
	(progn
	  (set-buffer (process-buffer proc))
	  (cond 
	   ;; a <retype-line error>
	   ((and
	     (memq math-send-state '(non-last-line last-line))
	     (string-match "\\`\\([ \t]*\\)\\^ <retype line>" string))
	    (let ((tpt (point))
		  error-column
		  indent-column
		  (tail-string (substring string (match-end 0))))
	      (goto-char tpt)
	      (insert (substring string 0 (match-end 1)))
	      (setq error-column (current-column))
	      (delete-region tpt (point))
	      (insert math-indent-string)
	      (setq indent-column (current-column))
	      (delete-region tpt (point))
	      (indent-to-column (- error-column indent-column))
	      (insert "^--error\n")
	      (backward-char 9)
	      (previous-line 1)
	      ;; Display any unexpected output.  I don't know how to 
	      ;; test this code.
	      (if (string-match "\\S " tail-string)
		  (save-excursion
		    (goto-char (point-max))
		    (insert tail-string))))  ; end of let
	    (setq math-send-state 'throw-away-prompt)
	    (message "Syntax error") ; live dangerously here, but sometimes we 
					; don't get a prompt back from 
					; Mathematica
	    (process-send-string proc "\n"))
	   ;; snarf up indent strings
	   ((and
	     (eq math-send-state 'non-last-line)
	     (string-match "\\`[ \t]+\\'" string))
	    (setq math-indent-string string))
	   ;; unexpected output
	   ((eq math-send-state 'non-last-line)
	    (insert 
"-------- Unexpected output appeared here; rest of cell not sent --------\n"
)
	    (goto-char (point-max))
	    (insert string)
	    (set-marker (process-mark proc) (point))
	    (setq math-send-state 'premature-output)
	    (message ""))
	   ;; throw away unwanted prompt
	   ((eq math-send-state 'throw-away-prompt)
	     (setq math-send-state 'normal)
	     (set-process-filter proc nil)
	     (if (string-match "\\`In\\[[0-9]+\\]:= \\'" string)
		 (message "Syntax error")
	       (message "Syntax error, discarding prompt(?): %s" string)))
	   ((eq math-send-state 'last-line)
	    (goto-char (point-max))
	    (cond ((and (string-match "\\`[ \t]*\\S " string)
			(not (string-match "\\`In\\[[0-9]+\\]:=" string)))
		   (newline)
		   (insert string)
		   (set-marker (process-mark proc) (point))
		   (setq math-send-state 'normal)
		   (message "newline inserted by Emacs' math-mode"))
		  ((string-match "\\`[ \t]*\n" string)
		   (setq math-send-state 'normal)
		   (insert string)
		   (set-marker (process-mark proc) (point))
		   (message ""))
		  ((string-match "\\S " string)
		   (insert string)
		   (set-marker (process-mark proc) (point))
		   (message ""))
		  (t ; just white space
		   (insert string)
		   (message 
		    "Incomplete cell?  (Clear with RET ESC RET)"))))
	   (t
	    (setq math-send-state 'normal)
	    (goto-char (point-max))
	    (insert string)
	    (set-marker (process-mark proc) (point))) 
	
	   ))  ; finishes up cond and progn
      ;; safely exit the filter
      (set-buffer cbuf)
      (store-match-data save-match-data))))

(defun math-mode ()
  "Major mode for interacting with Mathematica and editing .m files.
\\[math] starts Mathematica.

\\[math-send-input] tries to identify stuff following last \"In[...]:=
\" or blank line or the last output and sends it.  To clear out
Mathmatica after an error occurs, move point two lines below last
printing character and type \\[math-send-input].  Warning: do not
use Input[\"\"], and type in a mult-line reply; deadlock results.

\\[math-help] gives help on a Mathematica symbol.  
\\[math-extra-help] or C-u \\[math-help] gives more verbose help.

\\[math-complete-symbol] will complete the symbol near point.

\\[math-copy-cell] will copy a previous cell to the end of the buffer.
See its description for details.

\\[math-isearch-backward] does a backward regexp i-search, 
initialized to find In[...].

\\[find-math-error] when typed after <<filename has returned a
syntax error will goto the error.  (Depends on Mathematica-search-path.)

\\[goto-matherr-line] will go to the specificied line, with lines
counted as Mathematica does.  For use in .m files.

\\[interrupt-shell-subjob] interrupts Mathematica.
\\[kill-9-process] kills (-9) the Mathematica process.

\\[start-math] starts a Mathematica process in the current buffer.

Most entries from the Emacs' shell mode are available as well.

If you are not in a buffer running Mathematica, \\[math-help], \\[math-extra-help], 
\\[math-complete-symbol], and \\[math-copy-cell] use or copy to the 
buffer *math*.  \\[math-help], \\[math-extra-help], and \\[math-complete-symbol]
all send input to Mathematica: chaos may ensue if you do this while Mathmatica
is busy with other work---no check is made.  You can change the buffer/process
these commands use with \\[set-math-process-buffer].

Entry to this mode calls the value of math-mode-hook with no args,
if that value is non-nil."


  (interactive)
  (kill-all-local-variables)
  (setq major-mode 'math-mode)
  (setq mode-name "Mathematica")
  (setq mode-line-process '(": %s"))
  (use-local-map math-mode-map)
  (set-syntax-table math-mode-syntax-table)
  (make-local-variable 'parse-sexp-ignore-comment)
  (setq parse-sexp-ignore-comment t)
  (make-local-variable 'math-indent-string)
  (make-local-variable 'math-send-state)
  (setq math-send-state 'normal)
  (make-local-variable 'doing-math-complete-symbol)
  (setq doing-math-complete-symbol nil)
  (run-hooks 'math-mode-hook))


(defun math ()
  "Run Mathematica, input and output via buffer *math*."
  (interactive)
  (pop-to-buffer (start-buffer-process
		  "*math*" "math" math-process-string
		  nil))
  (math-mode)
  ;; We don't make this one local.  That way if the
  ;; user changes the name of the buffer, say by writing
  ;; it to a file, math-process-buffer still points
  ;; to the right place.
  (setq math-process-buffer (current-buffer)))

(defun start-math ()
  "Starts a Mathematica process in the current buffer."
  (interactive "*")
  (start-buffer-process (current-buffer) "math" math-process-string
			nil)
  (math-mode)
  (make-local-variable 'math-process-buffer)
  (setq math-process-buffer (current-buffer)))


(defun math-complete-symbol ()
  "Complete the symbol preceeding point."
  (interactive "*")
  (let ((process (get-buffer-process math-process-buffer))
	sent-successfully)
    (if	(not (and process (memq (process-status process) '(run stop))))
	(error "No math process running in buffer %s" math-process-buffer))
    (setq math-completion-symbol (math-symbol-around-point))
    (unwind-protect
	(let ((cbuf (current-buffer)))
	  (set-buffer (get-buffer-create " Mathwork"))
	  (erase-buffer)
	  (set-buffer cbuf)
	  (setq doing-math-complete-symbol t)
	  (set-process-filter process 'math-help-filter)
	  (process-send-string process (concat 
"Scan[Print,Names[\"" math-completion-symbol "**\"]];Out[--$Line];\n"))
	  (setq sent-successfully t))
      (if (not sent-successfully)
	  (progn
	    (setq doing-math-complete-symbol nil)
	    (set-process-filter process nil))))))
	   
		      
(defun math-symbol-around-point ()
 "Return the symbol around the point as a string."
 (save-excursion
   (let (beg)
     (if (not (eobp)) (forward-char 1))
     (re-search-backward "\\w\\|\\s_")
     (forward-char 1)
     (backward-sexp)
     (setq beg (point))
     (forward-sexp)
     (buffer-substring beg (point)))))

(defun math-extra-help () 
  "Like math-help with a prefix arg"
  (interactive)
  (let ((current-prefix-arg (list 1))
	(prefix-arg (list 1)))          ; I'm hacking.  
					; current-prefix-arg makes M-X ... work
                                        ; prefix-arg makes it work when bound to a key
					; I'm sure RMS had something else in mind.
    (call-interactively 'math-help)))

(defun math-help (symbol arg)
  "Display what Mathematica knows about SYMBOL.  
With prefix arg (2nd arg when called from a program) it gives more info."
  (interactive  ; read a word, using the word around point as the default
   (let ((enable-recursive-minibuffers t)
	 (try-word (math-symbol-around-point))
	 val)
     (if (string-equal try-word "")
	 (setq val (read-string "Mathematica symbol: "))
       (setq val (read-string (format "Mathematica symbol (default %s): "
				      try-word)))
       (if (string-equal val "")
	   (setq val try-word)))
     (if (string-equal val "")
	 (error "No symbol read"))
     (list val current-prefix-arg)))
  (let ((process (get-buffer-process math-process-buffer))
	sent-successfully)
    (if	(not (and process (memq (process-status process) '(run stop))))
      (error "No math process running in buffer %s" math-process-buffer))
    (unwind-protect
	(progn
	  (with-output-to-temp-buffer "*Help*"
	    (print-help-return-message))
	  (set-process-filter process 'math-help-filter)
	  (process-send-string process (concat (if arg "??" "?") symbol "\n"))
	  (setq sent-successfully t))
      (if (not sent-successfully) (set-process-filter process nil)))))


(defun math-help-filter (proc string)
  (let ((cbuf (current-buffer))
	(save-match-data (match-data))
	(local-doing-math-complete-symbol doing-math-complete-symbol))
    ;; doing-math-complete-symbol is buffer-local and we are going
    ;; to switch buffers.
    (unwind-protect
	(progn
	  (if local-doing-math-complete-symbol
	      (set-buffer " Mathwork")
	    (set-buffer "*Help*"))
	  (goto-char (point-max))
	  (insert string)
	  (beginning-of-line)
	  (if (looking-at "^In\\[[0-9]+\\]:=")
	      (progn
		(delete-region (point) (point-max))
		(bury-buffer (current-buffer))
		(set-process-filter proc nil)
		(if local-doing-math-complete-symbol
		    (progn
		      (set-buffer cbuf)
		      ;; we are back to the original buffer, so this is ok
		      (setq doing-math-complete-symbol nil)
		      (insert (get-math-completion math-completion-symbol)))
		  (goto-char (point-min))))))
      (set-buffer cbuf)
      (store-match-data save-match-data))))

(defun check-math-syntax (pmin pmax)
  "Checks for balanced parens and lack of valid prefix.
Mathematica will misbehave if there exists a prefix of a cell such that
the prefix ends in a newline and forms a valid mathematica expresssion.
This function causes an error if that is the case.  If that is ok it checks 
that the whole expression has balanced parens, comments and quotes.  It is
not perfect at these checks since GNU Emacs does not understand nested
comments.  Also it only checks that the nesting level of all paren constructs
is zero at the end, not that they really match."
  (interactive "r")
  (let ((pt (point))
	possibleerr)
    (save-restriction
      (narrow-to-region pmin pmax)
      (goto-char pmin)
      (while (and (not possibleerr)
		  (not (eobp)))
	(end-of-line)
	(let ((parsestate (parse-partial-sexp (point-min) (point))))
	  (if (not (looking-at "\\s *\\'")) ; not just all white space to eob
	      (progn      ; make sure this could NOT end a valid expression
		(if (and
		     (= (nth 0 parsestate) 0) ; zero paren depth
		     (not (nth 3 parsestate)) ; not in a string
		     (not (nth 4 parsestate)) ; not in a comment
		     (progn
		       (forward-line 0)
		       (looking-at  ; last symbol could be end of number or symbol or
					; right delim or postfix op
			".*\\([])}\"A-Za-z0-9!_'.]\\|\\+\\+\\|--\\|[^/];\\|\\.\\.\\)[ \t]*$")))
		    ;; might confuse mathematics
		    (progn
		      (setq possibleerr 
			    "Possible complete statement before end, submit anyway? ")
		      (end-of-line))))
	    ;; we are at the end of the statement
	    (cond ((nth 3 parsestate)
		   (setq possibleerr
			 "Apparently unterminated string, submit anyway? "))
		  ((nth 4 parsestate)
		   (setq possibleerr 
			 "Apparently unclosed comment, submit anyway? "))
		  ((not (zerop (nth 0 parsestate)))
		   (setq possibleerr
			 "Apparently mismatched parens, submit anyway? "))))
	  (if (not possibleerr) (forward-line 1)))))
    (if (and possibleerr (not (y-or-n-p possibleerr)))
	(error "Cancelled")
      (goto-char pt))))


(defun start-buffer-process (bufferid procname program &optional startfile &rest switches)
  ;; A munged version of make-shell
  ;; bufferid can be a buffer or the name of a buffer
  (let ((buffer (get-buffer-create bufferid))
	proc status size)
    (setq proc (get-buffer-process buffer))
    (if proc (setq status (process-status proc)))
    (save-excursion
      (set-buffer buffer)
      ;;    (setq size (buffer-size))
      (if (memq status '(run stop))
	  nil
	(if proc (delete-process proc))
	(message "Starting Mathematica...")
	(setq proc (apply 'start-process procname buffer
			  (concat exec-directory "env")
			  (format "TERMCAP=emacs:co#%d:tc=unknown:"
				  (screen-width))
			  "TERM=emacs"
			  "EMACS=t"
			  "-"
			  (or program explicit-shell-file-name
			      (getenv "ESHELL")
			      (getenv "SHELL")
			      "/bin/sh")
			  switches))
	(cond (startfile
	       ;;This is guaranteed to wait long enough
	       ;;but has bad results if the shell does not prompt at all
	       ;;	     (while (= size (buffer-size))
	       ;;	       (sleep-for 1))
	       ;;I hope 1 second is enough!
	       (sleep-for 1)
	       (goto-char (point-max))
	       (insert-file-contents startfile)
	       (setq startfile (buffer-substring (point) (point-max)))
	       (delete-region (point) (point-max))
	       (process-send-string proc startfile)))
	(setq procname (process-name proc)))  ; what in the world is this for?
      (goto-char (point-max))
      (set-marker (process-mark proc) (point))
      (shell-mode))
    buffer))

(defun backward-incarnations (inc)
  "Moves back ARG incarnations of Mathematica, as recognized
by math-header-re."
  (if inc
      (let ((count (cond ((numberp inc) inc)
			 ((equal inc '(4)) 1)
			 ((equal inc '(16)) 2)
			 ((equal inc '(64)) 3)
			 ((equal inc '(256)) 4)
			 ((equal inc '(1024)) 5)
			 (t (error "I'm too lazy to count that many prefix keys")))))
		(re-search-backward math-header-re nil nil count))))

(defun math-copy-cell (numberstring incarnations pt)
  "Copies the cell beginning In[<CELLNUMBER>] to the end of the buffer.  
With CELLNUMBER of empty string and point at or after last In[...]:= 
copies previous In cell to end of buffer.  With point before last In[...]:= 
copies cell near point (In, Out, or just a block of text) to end of buffer.  
With an explicit CELLNUMBER, a prefix arg will skip back prefix arg 
incarnations before searching for In[<CELLNUMBER>].  C-u's count in unary.  
When called from a program, CELLNUMBER must be a string, second arg is 
INCARNATIONS back and third is POINT to begin search at."
  (interactive "*sCell number (default is cell near point):  \nP\nd")
  (cond  ((zerop (length numberstring))
	  (goto-char (point-max))
	  (if (and
	       (re-search-backward "^In\\[[0-9]+\\]:=" nil t)
	       (>= pt (point)))
	      (progn
		(re-search-backward "^In\\[[0-9]+\\]:=") ; back up to previous one
		(while (and (not (bobp))
			      (or (looking-at ; reject ones without any useful text 
				   "^In\\[[0-9]+\\]:=\\s *\\(\\'\\|\n\\s *$\\)")))
		  (re-search-backward "^In\\[[0-9]+\\]:=")))
	    (goto-char pt))) ; do current cell
	 (t
	  (goto-char (point-max))
	  (backward-incarnations incarnations)
	  (re-search-backward (concat "^In\\[" numberstring "\\]:="))))
  (if (interactive-p) (push-mark))
  (let* ((cellinfo (math-identify-cell (point) nil t))
	 (copy (buffer-substring (car cellinfo) (nth 1 cellinfo))))
    (if (not (equal (get-buffer math-process-buffer)
		    (current-buffer)))
	(pop-to-buffer math-process-buffer))
    (goto-char (point-max))
    (re-search-backward "\\S ")
    (forward-line 0)
    (if (looking-at "^In\\[[0-9]+\\]:=\\s *$")
	(end-of-line)
      (goto-char (point-max)))
    (insert copy)))

(defun math-isearch-backward ()
  "Does a backward regexp i-search, initialized to find In[...]:="
  (interactive)
  (setq search-last-regexp "^In\\[[0-9]+\\]:=\\s *")
  (setq unread-command-char search-reverse-char)
  (isearch-backward-regexp))

(defun math-identify-cell (pt &optional procmark out-ok)
  "Finds cell around POS. 
Optional second arg PROCMARK (normally the process-mark) will bound the 
search if the boundary otherwise would be a blank line (or the 
beginning of the buffer) and POS >= PROCMARK. Optional 3rd arg OUT-OK
will allow acceptance of Out cells as well as In cells. Returns a list of
the buffer position of the beginning and end of the cell."
  (save-excursion
    (goto-char pt)
    ;; back up at most one blank line looking for input
    (end-of-line)
    (re-search-backward  
     (if out-ok
	 "\\(^In\\[[0-9]+\\]:= ?\\)\\|\\(^\\s *\n\\)\\|\\(^Out\\[[0-9]+\\]\\(//[^=]*\\)?= ?\\)"
       "\\(^In\\[[0-9]+\\]:= ?\\)\\|\\(^\\s *\n\\)") nil 1)
    (goto-char (cond ((match-end 1))
		     ((and out-ok (match-end 3)))
		     ((and procmark (>= pt procmark))
		      (max procmark 
			   (or (match-end 2) 
			       (point-min) )))
		     ((match-end 2))
		     ((point-min))))
    (let ((bpt (point))
	  ept
	  )
      (if (re-search-forward "^\\s *$\\|^Out\\[[0-9]+\\][^=\n]*=\\|^In\\[[0-9]+\\]:=" nil 1)
	  ;; If it matches, we have found the beginning of a line
	  ;;  following the cell.  Back up one character.  
	  ;; If it doesn't match we are at eob and end of cell.
	  (goto-char (max (- (match-beginning 0) 1) bpt)))
      (setq ept (point))
      (list bpt ept))))



(defun get-math-completion (prefix)
  "Returns string to insert to complete a Mathematica symbol
  Designed to be called as in (insert (get-math-completion word))"
  (let ((cbuf (current-buffer)))
    (unwind-protect
	(progn
	  (set-buffer " Mathwork")
	  (goto-char (point-min))
	  (let (alist)
	    (while (looking-at "\\S +")
	      (setq alist (cons (list (buffer-substring (match-beginning 0) (match-end 0))) alist))
	      (forward-line 1))
	    (set-buffer cbuf)
	    (let ((t-c-result  (and alist (try-completion prefix alist))))
	      ; try-completion barfs on a nil alist, so we help it out
	      (cond ((eq t-c-result t) 
		     (message "%s is complete" prefix)
		     "")
		    ((eq t-c-result nil)
		     (message "No match found")
		     "")
		    ((not (string= prefix t-c-result))
		     (substring t-c-result (length prefix)))
		    (t (with-output-to-temp-buffer "*Help*"
			 (display-completion-list 
			  (all-completions prefix alist))
			 (print-help-return-message))
		       ""))))))))

(defun kill-9-process ()
  "Kills the process in the current buffer as in kill -9."
  (interactive)
  (kill-process (get-buffer-process (current-buffer))))

(defun metered-process-send-string (process string)
  "The same semantics as process-send-string, except the
string is broken into small enough chunks to not mess up emacs."
  (let ((p 0)
	(len (length string)))
    (while (< p len)
      (process-send-string process
			   (substring string p (setq p (min len (+ p 80))))))))



(defun skip-over-white-lines ()
  ;; it might be possible to do this with 
  ;; (re-search-forward "\\(^\\s *\n\\)*")
  ;; but this works.
  (while (and 
	  (not (eobp))
	  (looking-at "^\\s *$") ; blank line
	  (zerop (forward-line)))))

;;; Mathematica counts lines wrong.  The following is what really happens.
;;; Blank lines, other than the first line are not counted (unless inside 
;;; quotes or comments).  Unescaped newlines inside strings count double.

(defun goto-matherr-line (argline)
  "Goes to the line intended by Mathematica error messages"
  (interactive "ngoto Mathematica line number: ")
  (let ((lineno 1)
	(comment-depth 0)
	instring)
    (goto-char (point-min))
    (if (looking-at "^\s *$")
	(progn
	  (setq lineno 2)
	  (skip-over-white-lines)))
    (while (and (not (eobp))
		(< lineno argline))
      (cond ((> comment-depth 0)
	     (re-search-forward "\\((\\*\\)\\|\\(\\*)\\)\\|\\(\n\\)" nil 1)
					; (* or *) or newline
	     (cond ((match-beginning 1)
		    (setq comment-depth (1+ comment-depth)))
		   ((match-beginning 2)
		    (setq comment-depth (1- comment-depth)))
		   ((match-beginning 3)
		    (setq lineno (1+ lineno)))))
	    (instring
	     (re-search-forward 
"\\(\\\\\\\\\\)\\|\\(\\\\\042\\)\\|\\(\042\\)\\|\\(\\\\\n\\)\\|\\(\n\\)" nil 1)
	     ;; \\ or \quote or quote or \newline or newline
	     ;;  \042 is a double quote.  
	     ;; Using the octal form keeps Emacs from getting lost.
	     (cond ((match-beginning 3)
		    (setq instring nil))
		   ((match-beginning 4)
		    (setq lineno (1+ lineno)))
		   ((match-beginning 5)
		    (setq lineno (+ 2 lineno)))))
	    (t
	     (re-search-forward "\\(\050\\*\\)\\|\\(\042\\)\\|\\(\n\\)" nil 1)
					; left paren* or quote or newline
	     (cond ((match-beginning 1)
		    (setq comment-depth 1))
		   ((match-beginning 2)
		    (setq instring t))
		   ((match-beginning 3)
		    (setq lineno (1+ lineno))
		    (skip-over-white-lines))))))))

(defun find-math-error ()
  "Searches for the last \"syntax error in\" message; goes to indicated line
in the indicated file.  It uses the symbol Mathematica-search-path rather 
than going to all the work to discover the real real search path."
  (interactive)
  (let (filename
	linenumber
	raw-filename
	(math-search-path Mathematica-search-path))
    (save-excursion
      (re-search-backward "syntax error in")
      (forward-line 0)
      (if (not (looking-at "\\([^:]+\\): *\\([0-9]+\\):"))
	  (error "Cannot parse error line"))
      (setq raw-filename (buffer-substring (match-beginning 1) (match-end 1)))
      (setq linenumber (string-to-int 
			(buffer-substring (match-beginning 2) (match-end 2)))))
    (while (not filename)
      (setq filename (expand-file-name raw-filename (car math-search-path)))
      (if (not (file-readable-p filename))
	  (progn (setq filename nil)
		 (setq math-search-path (cdr math-search-path))
		 (if (null math-search-path)
		     (error "File %s not found" raw-filename)))))
    (find-file-other-window filename)
    (goto-matherr-line linenumber)))


(defun set-math-process-buffer (buffer)
  "Sets the buffer in/to which to evaluate/copy Mathematica
code.  (You only need to use this function if you want a buffer 
other than *math*.)"
  (interactive "bMathematica buffer: ")
  (make-local-variable 'math-process-buffer)
  ;; The following trick will use the buffer itself if
  ;; it is defined.  That way if the user eventually 
  ;; changes the name, say by writing it out, this local
  ;; math-process-buffer will still point to the right place.  
  ;; But if the buffer does not yet exist, it will still work.
  (setq math-process-buffer (or (get-buffer buffer) buffer)))




  • Prev by Date: Trigonometry expansions
  • Next by Date: Re: supressing argument evaluation by function Part
  • Previous by thread: Trigonometry expansions
  • Next by thread: Re: supressing argument evaluation by function Part