Initial Commit
[packages] / xemacs-packages / ocaml / caml.el
1 ;;; caml.el --- O'Caml code editing commands for Emacs
2
3 ;; Xavier Leroy, july 1993.
4
5 ;;indentation code is Copyright (C) 1996 by Ian T Zimmerman <itz@rahul.net>
6 ;;copying: covered by the current FSF General Public License.
7
8 ;; indentation code adapted for Objective Caml by Jacques Garrigue,
9 ;; july 1997. <garrigue@kurims.kyoto-u.ac.jp>
10
11 ;;user customizable variables
12 (defvar caml-quote-char "'"
13   "*Quote for character constants. \"'\" for Objective Caml, \"`\" for Caml-Light.")
14
15 (defvar caml-imenu-enable nil
16   "*Enable Imenu support.")
17
18 (defvar caml-mode-indentation 2
19   "*Used for \\[caml-unindent-command].")
20
21 (defvar caml-lookback-limit 5000
22   "*How far to look back for syntax things in caml mode.")
23
24 (defvar caml-max-indent-priority 8
25   "*Bounds priority of operators permitted to affect caml indentation.
26
27 Priorities are assigned to `interesting' caml operators as follows:
28
29         all keywords 0 to 7     8
30         type, val, ... + 0      7
31         :: ^                    6
32         @                       5
33         := <-                   4
34         if                      3
35         fun, let, match ...     2
36         module                  1
37         opening keywords        0.")
38
39 (defvar caml-apply-extra-indent 2
40   "*How many spaces to add to indentation for an application in caml mode.")
41 (make-variable-buffer-local 'caml-apply-extra-indent)
42
43 (defvar caml-begin-indent 2
44   "*How many spaces to indent from a begin keyword in caml mode.")
45 (make-variable-buffer-local 'caml-begin-indent)
46
47 (defvar caml-class-indent 2
48   "*How many spaces to indent from a class keyword in caml mode.")
49 (make-variable-buffer-local 'caml-class-indent)
50
51 (defvar caml-exception-indent 2
52   "*How many spaces to indent from a exception keyword in caml mode.")
53 (make-variable-buffer-local 'caml-exception-indent)
54
55 (defvar caml-for-indent 2
56   "*How many spaces to indent from a for keyword in caml mode.")
57 (make-variable-buffer-local 'caml-for-indent)
58
59 (defvar caml-fun-indent 2
60   "*How many spaces to indent from a fun keyword in caml mode.")
61 (make-variable-buffer-local 'caml-fun-indent)
62
63 (defvar caml-function-indent 4
64   "*How many spaces to indent from a function keyword in caml mode.")
65 (make-variable-buffer-local 'caml-function-indent)
66
67 (defvar caml-if-indent  2
68   "*How many spaces to indent from a if keyword in caml mode.")
69 (make-variable-buffer-local 'caml-if-indent)
70
71 (defvar caml-if-else-indent 0
72   "*How many spaces to indent from an if .. else line in caml mode.")
73 (make-variable-buffer-local 'caml-if-else-indent)
74
75 (defvar caml-inherit-indent 2
76   "*How many spaces to indent from a inherit keyword in caml mode.")
77 (make-variable-buffer-local 'caml-inherit-indent)
78
79 (defvar caml-initializer-indent 2
80   "*How many spaces to indent from a initializer keyword in caml mode.")
81 (make-variable-buffer-local 'caml-initializer-indent)
82
83 (defvar caml-include-indent 2
84   "*How many spaces to indent from a include keyword in caml mode.")
85 (make-variable-buffer-local 'caml-include-indent)
86
87 (defvar caml-let-indent 2
88   "*How many spaces to indent from a let keyword in caml mode.")
89 (make-variable-buffer-local 'caml-let-indent)
90
91 (defvar caml-let-in-indent 0
92   "*How many spaces to indent from a let .. in keyword in caml mode.")
93 (make-variable-buffer-local 'caml-let-in-indent)
94
95 (defvar caml-match-indent 2
96   "*How many spaces to indent from a match keyword in caml mode.")
97 (make-variable-buffer-local 'caml-match-indent)
98
99 (defvar caml-method-indent 2
100   "*How many spaces to indent from a method keyword in caml mode.")
101 (make-variable-buffer-local 'caml-method-indent)
102
103 (defvar caml-module-indent 2
104   "*How many spaces to indent from a module keyword in caml mode.")
105 (make-variable-buffer-local 'caml-module-indent)
106
107 (defvar caml-object-indent 2
108   "*How many spaces to indent from a object keyword in caml mode.")
109 (make-variable-buffer-local 'caml-object-indent)
110
111 (defvar caml-of-indent 2
112   "*How many spaces to indent from a of keyword in caml mode.")
113 (make-variable-buffer-local 'caml-of-indent)
114
115 (defvar caml-parser-indent 4
116   "*How many spaces to indent from a parser keyword in caml mode.")
117 (make-variable-buffer-local 'caml-parser-indent)
118
119 (defvar caml-sig-indent 2
120   "*How many spaces to indent from a sig keyword in caml mode.")
121 (make-variable-buffer-local 'caml-sig-indent)
122
123 (defvar caml-struct-indent 2
124   "*How many spaces to indent from a struct keyword in caml mode.")
125 (make-variable-buffer-local 'caml-struct-indent)
126
127 (defvar caml-try-indent 2
128   "*How many spaces to indent from a try keyword in caml mode.")
129 (make-variable-buffer-local 'caml-try-indent)
130
131 (defvar caml-type-indent 4
132   "*How many spaces to indent from a type keyword in caml mode.")
133 (make-variable-buffer-local 'caml-type-indent)
134
135 (defvar caml-val-indent 2
136   "*How many spaces to indent from a val keyword in caml mode.")
137 (make-variable-buffer-local 'caml-val-indent)
138
139 (defvar caml-while-indent 2
140   "*How many spaces to indent from a while keyword in caml mode.")
141 (make-variable-buffer-local 'caml-while-indent)
142
143 (defvar caml-::-indent  2
144   "*How many spaces to indent from a :: operator in caml mode.")
145 (make-variable-buffer-local 'caml-::-indent)
146
147 (defvar caml-@-indent   2
148   "*How many spaces to indent from a @ operator in caml mode.")
149 (make-variable-buffer-local 'caml-@-indent)
150
151 (defvar caml-:=-indent  2
152   "*How many spaces to indent from a := operator in caml mode.")
153 (make-variable-buffer-local 'caml-:=-indent)
154
155 (defvar caml-<--indent  2
156   "*How many spaces to indent from a <- operator in caml mode.")
157 (make-variable-buffer-local 'caml-<--indent)
158
159 (defvar caml-->-indent  2
160   "*How many spaces to indent from a -> operator in caml mode.")
161 (make-variable-buffer-local 'caml-->-indent)
162
163 (defvar caml-lb-indent 2
164   "*How many spaces to indent from a \[ operator in caml mode.")
165 (make-variable-buffer-local 'caml-lb-indent)
166
167 (defvar caml-lc-indent 2
168   "*How many spaces to indent from a \{ operator in caml mode.")
169 (make-variable-buffer-local 'caml-lc-indent)
170
171 (defvar caml-lp-indent  1
172   "*How many spaces to indent from a \( operator in caml mode.")
173 (make-variable-buffer-local 'caml-lp-indent)
174
175 (defvar caml-and-extra-indent nil
176   "*Extra indent for caml lines starting with the and keyword.
177 Usually negative. nil is align on master.")
178 (make-variable-buffer-local 'caml-and-extra-indent)
179
180 (defvar caml-do-extra-indent nil
181   "*Extra indent for caml lines starting with the do keyword.
182 Usually negative. nil is align on master.")
183 (make-variable-buffer-local 'caml-do-extra-indent)
184
185 (defvar caml-done-extra-indent nil
186   "*Extra indent for caml lines starting with the done keyword.
187 Usually negative. nil is align on master.")
188 (make-variable-buffer-local 'caml-done-extra-indent)
189
190 (defvar caml-else-extra-indent nil
191   "*Extra indent for caml lines starting with the else keyword.
192 Usually negative. nil is align on master.")
193 (make-variable-buffer-local 'caml-else-extra-indent)
194
195 (defvar caml-end-extra-indent nil
196   "*Extra indent for caml lines starting with the end keyword.
197 Usually negative. nil is align on master.")
198 (make-variable-buffer-local 'caml-end-extra-indent)
199
200 (defvar caml-in-extra-indent nil
201   "*Extra indent for caml lines starting with the in keyword.
202 Usually negative. nil is align on master.")
203 (make-variable-buffer-local 'caml-in-extra-indent)
204
205 (defvar caml-then-extra-indent nil
206   "*Extra indent for caml lines starting with the then keyword.
207 Usually negative. nil is align on master.")
208 (make-variable-buffer-local 'caml-then-extra-indent)
209
210 (defvar caml-to-extra-indent -1
211   "*Extra indent for caml lines starting with the to keyword.
212 Usually negative. nil is align on master.")
213 (make-variable-buffer-local 'caml-to-extra-indent)
214
215 (defvar caml-with-extra-indent nil
216   "*Extra indent for caml lines starting with the with keyword.
217 Usually negative. nil is align on master.")
218 (make-variable-buffer-local 'caml-with-extra-indent)
219
220 (defvar caml-comment-indent 3
221   "*Indent inside comments.")
222 (make-variable-buffer-local 'caml-comment-indent)
223
224 (defvar caml-|-extra-indent -2
225   "*Extra indent for caml lines starting with the | operator.
226 Usually negative. nil is align on master.")
227 (make-variable-buffer-local 'caml-|-extra-indent)
228
229 (defvar caml-rb-extra-indent -2
230   "*Extra indent for caml lines statring with ].
231 Usually negative. nil is align on master.")
232
233 (defvar caml-rc-extra-indent -2
234   "*Extra indent for caml lines starting with }.
235 Usually negative. nil is align on master.")
236
237 (defvar caml-rp-extra-indent -1
238   "*Extra indent for caml lines starting with ).
239 Usually negative. nil is align on master.")
240
241 (defvar caml-electric-indent t
242   "*Non-nil means electrically indent lines starting with |, ] or }.
243
244 Many people find eletric keys irritating, so you can disable them if
245 you are one.")
246
247 (defvar caml-electric-close-vector t
248   "*Non-nil means electrically insert a | before a vector-closing ].
249
250 Many people find eletric keys irritating, so you can disable them if
251 you are one. You should probably have this on, though, if you also
252 have caml-electric-indent on, which see.")
253
254 ;;code
255 (if (or (not (fboundp 'indent-line-to))
256         (not (fboundp 'buffer-substring-no-properties)))
257     (require 'caml-compat))
258
259 (defvar caml-shell-active nil
260   "Non nil when a subshell is running.")
261
262 (defvar running-xemacs nil
263   "Non nil when using xemacs.")
264
265 (defvar caml-mode-map nil
266   "Keymap used in Caml mode.")
267 (if caml-mode-map
268     ()
269   (setq caml-mode-map (make-sparse-keymap))
270   (define-key caml-mode-map "|" 'caml-electric-pipe)
271   (define-key caml-mode-map "}" 'caml-electric-pipe)
272   (define-key caml-mode-map "]" 'caml-electric-rb)
273   (define-key caml-mode-map "\t" 'caml-indent-command)
274   (define-key caml-mode-map [backtab] 'caml-unindent-command)
275
276 ;itz 04-21-96 instead of defining a new function, use defadvice
277 ;that way we get out effect even when we do \C-x` in compilation buffer
278 ;  (define-key caml-mode-map "\C-x`" 'caml-next-error)
279
280   (if running-xemacs
281       (define-key caml-mode-map 'backspace 'backward-delete-char-untabify)
282     (define-key caml-mode-map "\177" 'backward-delete-char-untabify))
283   (define-key caml-mode-map "\C-cb" 'caml-insert-begin-form)
284   (define-key caml-mode-map "\C-cf" 'caml-insert-for-form)
285   (define-key caml-mode-map "\C-ci" 'caml-insert-if-form)
286   (define-key caml-mode-map "\C-cl" 'caml-insert-let-form)
287   (define-key caml-mode-map "\C-cm" 'caml-insert-match-form)
288   (define-key caml-mode-map "\C-ct" 'caml-insert-try-form)
289   (define-key caml-mode-map "\C-cw" 'caml-insert-while-form)
290   (define-key caml-mode-map "\C-c`" 'caml-goto-phrase-error)
291   (define-key caml-mode-map "\C-c\C-a" 'caml-find-alternate-file)
292   (define-key caml-mode-map "\C-c\C-c" 'compile)
293   (define-key caml-mode-map "\C-c\C-e" 'caml-eval-phrase)
294   (define-key caml-mode-map "\C-c\C-\[" 'caml-backward-to-less-indent)
295   (define-key caml-mode-map "\C-c\C-\]" 'caml-forward-to-less-indent)
296   (define-key caml-mode-map "\C-c\C-q" 'caml-indent-phrase)
297   (define-key caml-mode-map "\C-c\C-r" 'caml-eval-region)
298   (define-key caml-mode-map "\C-c\C-s" 'caml-show-subshell)
299   (define-key caml-mode-map "\M-\C-h" 'caml-mark-phrase)
300   (define-key caml-mode-map "\M-\C-q" 'caml-indent-phrase)
301   (define-key caml-mode-map "\M-\C-x" 'caml-eval-phrase)
302   (if running-xemacs nil ; if not running xemacs
303     (let ((map (make-sparse-keymap "Caml"))
304           (forms (make-sparse-keymap "Forms")))
305       (define-key caml-mode-map "\C-c\C-d" 'caml-show-imenu)
306       (define-key caml-mode-map [menu-bar] (make-sparse-keymap))
307       (define-key caml-mode-map [menu-bar caml] (cons "Caml" map))
308       (define-key map [run-caml] '("Start subshell..." . run-caml))
309       (define-key map [compile] '("Compile..." . compile))
310       (define-key map [switch-view]
311         '("Switch view" . caml-find-alternate-file))
312       (define-key map [separator-format] '("--"))
313       (define-key map [forms] (cons "Forms" forms))
314       (define-key map [show-imenu] '("Show index" . caml-show-imenu))
315       (put 'caml-show-imenu 'menu-enable '(not caml-imenu-shown))
316       (define-key map [show-subshell] '("Show subshell" . caml-show-subshell))
317       (put 'caml-show-subshell 'menu-enable 'caml-shell-active)
318       (define-key map [eval-phrase] '("Eval phrase" . caml-eval-phrase))
319       (put 'caml-eval-phrase 'menu-enable 'caml-shell-active)
320       (define-key map [indent-phrase] '("Indent phrase" . caml-indent-phrase))
321       (define-key forms [while]
322         '("while .. do .. done" . caml-insert-while-form))
323       (define-key forms [try] '("try .. with .." . caml-insert-try-form))
324       (define-key forms [match] '("match .. with .." . caml-insert-match-form))
325       (define-key forms [let] '("let .. in .." . caml-insert-let-form))
326       (define-key forms [if] '("if .. then .. else .." . caml-insert-if-form))
327       (define-key forms [begin] '("for .. do .. done" . caml-insert-for-form))
328       (define-key forms [begin] '("begin .. end" . caml-insert-begin-form)))))
329
330 (defvar caml-mode-xemacs-menu
331   (if running-xemacs
332       '("Caml"
333         [ "Indent phrase" caml-indent-phrase :keys "C-M-q" ]
334         [ "Eval phrase" caml-eval-phrase
335           :active caml-shell-active :keys "C-M-x" ]
336         [ "Show subshell" caml-show-subshell caml-shell-active ]
337         ("Forms"
338          [ "while .. do .. done" caml-insert-while-form t]
339          [ "try .. with .." caml-insert-try-form t ]
340          [ "match .. with .." caml-insert-match-form t ]
341          [ "let .. in .." caml-insert-let-form t ]
342          [ "if .. then .. else .." caml-insert-if-form t ]
343          [ "for .. do .. done" caml-insert-for-form t ]
344          [ "begin .. end" caml-insert-begin-form t ])
345         "---"
346         [ "Switch view" caml-find-alternate-file t ]
347         [ "Compile..." compile t ]
348         [ "Start subshell..." run-caml t ]))
349   "Menu to add to the menubar when running Xemacs")
350
351 (defvar caml-mode-syntax-table nil
352   "Syntax table in use in Caml mode buffers.")
353 (if caml-mode-syntax-table
354     ()
355   (setq caml-mode-syntax-table (make-syntax-table))
356   ; backslash is an escape sequence
357   (modify-syntax-entry ?\\ "\\" caml-mode-syntax-table)
358   ; ( is first character of comment start
359   (modify-syntax-entry ?\( "()1" caml-mode-syntax-table)
360   ; * is second character of comment start,
361   ; and first character of comment end
362   (modify-syntax-entry ?*  ". 23" caml-mode-syntax-table)
363   ; ) is last character of comment end
364   (modify-syntax-entry ?\) ")(4" caml-mode-syntax-table)
365   ; backquote was a string-like delimiter (for character literals)
366   ; (modify-syntax-entry ?` "\"" caml-mode-syntax-table)
367   ; quote and underscore are part of words
368   (modify-syntax-entry ?' "w" caml-mode-syntax-table)
369   (modify-syntax-entry ?_ "w" caml-mode-syntax-table)
370   ; ISO-latin accented letters and EUC kanjis are part of words
371   (let ((i 160))
372     (while (< i 256)
373       (modify-syntax-entry i "w" caml-mode-syntax-table)
374       (setq i (1+ i)))))
375
376 (defvar caml-mode-abbrev-table nil
377   "Abbrev table used for Caml mode buffers.")
378 (if caml-mode-abbrev-table nil
379   (setq caml-mode-abbrev-table (make-abbrev-table))
380   (define-abbrev caml-mode-abbrev-table "and" "and" 'caml-abbrev-hook)
381   (define-abbrev caml-mode-abbrev-table "do" "do" 'caml-abbrev-hook)
382   (define-abbrev caml-mode-abbrev-table "done" "done" 'caml-abbrev-hook)
383   (define-abbrev caml-mode-abbrev-table "else" "else" 'caml-abbrev-hook)
384   (define-abbrev caml-mode-abbrev-table "end" "end" 'caml-abbrev-hook)
385   (define-abbrev caml-mode-abbrev-table "in" "in" 'caml-abbrev-hook)
386   (define-abbrev caml-mode-abbrev-table "then" "then" 'caml-abbrev-hook)
387   (define-abbrev caml-mode-abbrev-table "with" "with" 'caml-abbrev-hook))
388
389 ;; Other internal variables
390
391 (defvar caml-last-noncomment-pos nil
392   "Caches last buffer position determined not inside a caml comment.")
393 (make-variable-buffer-local 'caml-last-noncomment-pos)
394
395 ;;last-noncomment-pos can be a simple position, because we nil it
396 ;;anyway whenever buffer changes upstream. last-comment-start and -end
397 ;;have to be markers, because we preserve them when the changes' end
398 ;;doesn't overlap with the comment's start.
399
400 (defvar caml-last-comment-start nil
401   "A marker caching last determined caml comment start.")
402 (make-variable-buffer-local 'caml-last-comment-start)
403
404 (defvar caml-last-comment-end nil
405   "A marker caching last determined caml comment end.")
406 (make-variable-buffer-local 'caml-last-comment-end)
407
408 (make-variable-buffer-local 'before-change-function)
409
410 (defvar caml-imenu-shown nil
411   "True if we have computed definition list.")
412 (make-variable-buffer-local 'caml-imenu-shown)
413
414 (defconst caml-imenu-search-regexp
415   (concat "\\<in\\>\\|"
416           "^[ \t]*\\(let\\|class\\|type\\|m\\(odule\\|ethod\\)"
417           "\\|functor\\|and\\|val\\)[ \t]+"
418           "\\(\\('[a-zA-Z0-9]+\\|([^)]+)"
419           "\\|mutable\\|private\\|rec\\|type\\)[ \t]+\\)?"
420           "\\([a-zA-Z][a-zA-Z0-9_']*\\)"))
421
422 ;;; The major mode
423 (eval-when-compile
424   (if (and (boundp 'running-xemacs) running-xemacs) nil
425     (require 'imenu)))
426
427 ;;;###autoload
428 (defun caml-mode ()
429   "Major mode for editing Caml code.
430
431 \\{caml-mode-map}"
432
433   (interactive)
434   (kill-all-local-variables)
435   (setq major-mode 'caml-mode)
436   (setq mode-name "caml")
437   (use-local-map caml-mode-map)
438   (set-syntax-table caml-mode-syntax-table)
439   (setq local-abbrev-table caml-mode-abbrev-table)
440   (make-local-variable 'paragraph-start)
441   (setq paragraph-start (concat "^$\\|" page-delimiter))
442   (make-local-variable 'paragraph-separate)
443   (setq paragraph-separate paragraph-start)
444   (make-local-variable 'paragraph-ignore-fill-prefix)
445   (setq paragraph-ignore-fill-prefix t)
446   (make-local-variable 'require-final-newline)
447   (setq require-final-newline t)
448   (make-local-variable 'comment-start)
449   (setq comment-start "(*")
450   (make-local-variable 'comment-end)
451   (setq comment-end "*)")
452   (make-local-variable 'comment-column)
453   (setq comment-column 40)
454   (make-local-variable 'comment-start-skip)
455   (setq comment-start-skip "(\\*+ *")
456   (make-local-variable 'parse-sexp-ignore-comments)
457   (setq parse-sexp-ignore-comments nil)
458   (make-local-variable 'indent-line-function)
459   (setq indent-line-function 'caml-indent-command)
460   ;itz Fri Sep 25 13:23:49 PDT 1998
461   (make-local-variable 'add-log-current-defun-function)
462   (setq add-log-current-defun-function 'caml-current-defun)
463   ;itz 03-25-96
464   (setq before-change-function 'caml-before-change-function)
465   (setq caml-last-noncomment-pos nil)
466   (setq caml-last-comment-start (make-marker))
467   (setq caml-last-comment-end (make-marker))
468   ;garrigue 27-11-96
469   (setq case-fold-search nil)
470   ;garrigue july 97
471   (if running-xemacs ; from Xemacs lisp mode
472       (if (and (featurep 'menubar)
473                current-menubar)
474           (progn
475             ;; make a local copy of the menubar, so our modes don't
476             ;; change the global menubar
477             (set-buffer-menubar current-menubar)
478             (add-submenu nil caml-mode-xemacs-menu)))
479     ;imenu support (not for Xemacs)
480     (make-local-variable 'imenu-create-index-function)
481     (setq imenu-create-index-function 'caml-create-index-function)
482     (make-local-variable 'imenu-generic-expression)
483     (setq imenu-generic-expression caml-imenu-search-regexp)
484     (if (and caml-imenu-enable (< (buffer-size) 10000))
485         (caml-show-imenu)))
486   (run-hooks 'caml-mode-hook))
487
488 ;;; Auxiliary function. Garrigue 96-11-01.
489
490 (defun caml-find-alternate-file ()
491   (interactive)
492   (let ((name (buffer-file-name)))
493     (if (string-match "^\\(.*\\)\\.\\(ml\\|mli\\)$" name)
494         (find-file
495          (concat
496           (caml-match-string 1 name)
497           (if (string= "ml" (caml-match-string 2 name)) ".mli" ".ml"))))))
498
499 ;;; subshell support
500
501 (defun caml-eval-region (start end)
502   "Send the current region to the inferior Caml process."
503   (interactive"r")
504   (require 'inf-caml)
505   (inferior-caml-eval-region start end))
506
507 ;; old version ---to be deleted later
508
509 ; (defun caml-eval-phrase ()
510 ;   "Send the current Caml phrase to the inferior Caml process."
511 ;   (interactive)
512 ;   (save-excursion
513 ;     (let ((bounds (caml-mark-phrase)))
514 ;     (inferior-caml-eval-region (car bounds) (cdr bounds)))))
515
516 (defun caml-eval-phrase (arg &optional min max)
517   "Send the phrase containing the point to the CAML process.
518 With prefix-arg send as many phrases as its numeric value, 
519 If an error occurs during evalutaion, stop at this phrase and
520 repport the error. 
521
522 Return nil if noerror and position of error if any.
523
524 If arg's numeric value is zero or negative, evaluate the current phrase
525 or as many as prefix arg, ignoring evaluation errors. 
526 This allows to jump other erroneous phrases. 
527
528 Optional arguments min max defines a region within which the phrase
529 should lies."
530   (interactive "p")
531   (require 'inf-caml)
532   (inferior-caml-eval-phrase arg min max))
533
534 (defun caml-eval-buffer (arg)
535   "Evaluate the buffer from the beginning to the phrase under the point.
536 With prefix arg, evaluate past the whole buffer, no stopping at
537 the current point."
538   (interactive "p")
539   (let ((here (point)) err)
540     (goto-char (point-min))
541     (setq err
542           (caml-eval-phrase 500 (point-min) (if arg (point-max) here)))
543     (if err (set-mark err))
544     (goto-char here)))
545
546 (defun caml-show-subshell ()
547   (interactive)
548   (require 'inf-caml)
549   (inferior-caml-show-subshell))
550
551
552 ;;; Imenu support
553 (defun caml-show-imenu ()
554   (interactive)
555   (require 'imenu)
556   (switch-to-buffer (current-buffer))
557   (imenu-add-to-menubar "Defs")
558   (setq caml-imenu-shown t))
559
560 (defun caml-prev-index-position-function ()
561   (let (found data)
562     (while (and (setq found
563                       (re-search-backward caml-imenu-search-regexp nil 'move))
564                 (progn (setq data (match-data)) t)
565                 (or (caml-in-literal-p)
566                     (caml-in-comment-p)
567                     (if (looking-at "in") (caml-find-in-match)))))
568     (set-match-data data)
569     found))
570 (defun caml-create-index-function ()
571   (let (value-alist
572         type-alist
573         class-alist
574         method-alist
575         module-alist
576         and-alist
577         all-alist
578         menu-alist
579         (prev-pos (point-max))
580         index)
581     (goto-char prev-pos)
582     (imenu-progress-message prev-pos 0 t)
583     ;; collect definitions
584     (while (caml-prev-index-position-function)
585       (setq index (cons (caml-match-string 5) (point)))
586       (imenu-progress-message prev-pos nil t)
587       (setq all-alist (cons index all-alist))
588       (cond
589        ((looking-at "[ \t]*and")
590         (setq and-alist (cons index and-alist)))
591        ((looking-at "[ \t]*let")
592         (setq value-alist (cons index (append and-alist value-alist)))
593         (setq and-alist nil))
594        ((looking-at "[ \t]*type")
595         (setq type-alist (cons index (append and-alist type-alist)))
596         (setq and-alist nil))
597        ((looking-at "[ \t]*class")
598         (setq class-alist (cons index (append and-alist class-alist)))
599         (setq and-alist nil))
600        ((looking-at "[ \t]*val")
601         (setq value-alist (cons index value-alist)))
602        ((looking-at "[ \t]*\\(module\\|functor\\)")
603         (setq module-alist (cons index module-alist)))
604        ((looking-at "[ \t]*method")
605         (setq method-alist (cons index method-alist)))))
606     ;; build menu
607     (mapcar
608      '(lambda (pair)
609         (if (symbol-value (cdr pair))
610             (setq menu-alist
611                   (cons
612                    (cons (car pair)
613                          (sort (symbol-value (cdr pair)) 'imenu--sort-by-name))
614                    menu-alist))))
615      '(("Values" . value-alist)
616        ("Types" . type-alist)
617        ("Modules" . module-alist)
618        ("Methods" . method-alist)
619        ("Classes" . class-alist)))
620     (if all-alist (setq menu-alist (cons (cons "Index" all-alist) menu-alist)))
621     (imenu-progress-message prev-pos 100 t)
622     menu-alist))
623
624 ;;; Indentation stuff
625
626 (defun caml-in-indentation ()
627   "Tests whether all characters between beginning of line and point
628 are blanks."
629   (save-excursion
630     (skip-chars-backward " \t")
631     (bolp)))
632
633 ;;; The command
634 ;;; Sorry, I didn't like the previous behaviour... Garrigue 96/11/01
635
636 (defun caml-indent-command (&optional p)
637   "Indent the current line in Caml mode.
638
639 Compute new indentation based on caml syntax. If prefixed, indent
640 the line all the way to where point is."
641
642   (interactive "*p")
643   (cond
644    ((and p (> p 1)) (indent-line-to (current-column)))
645    ((caml-in-indentation) (indent-line-to (caml-compute-final-indent)))
646    (t (save-excursion
647         (indent-line-to
648          (caml-compute-final-indent))))))
649
650 (defun caml-unindent-command ()
651
652   "Decrease indentation by one level in Caml mode.
653
654 Works only if the point is at the beginning of an indented line
655 \(i.e. all characters between beginning of line and point are
656 blanks\).  Does nothing otherwise. The unindent size is given by the
657 variable caml-mode-indentation."
658
659   (interactive "*")
660   (let* ((begline
661           (save-excursion
662             (beginning-of-line)
663             (point)))
664          (current-offset
665           (- (point) begline)))
666     (if (and (>= current-offset caml-mode-indentation)
667              (caml-in-indentation))
668         (backward-delete-char-untabify caml-mode-indentation))))
669
670 ;;;
671 ;;; Error processing
672 ;;;
673
674 ;; Error positions are given in bytes, not in characters
675 ;; This function switches to monobyte mode
676
677 (if (not (fboundp 'char-bytes))
678     (defalias 'forward-byte 'forward-char)
679   (defun caml-char-bytes (ch)
680     (let ((l (char-bytes ch)))
681       (if (> l 1) (- l 1) l)))
682   (defun forward-byte (count)
683     (if (> count 0)
684         (while (> count 0)
685           (setq count (- count (caml-char-bytes (char-after))))
686           (forward-char))
687       (while (< count 0)
688         (setq count (+ count (caml-char-bytes (char-before))))
689         (backward-char)))))
690
691 (require 'compile)
692
693 ;; In Emacs 19, the regexps in compilation-error-regexp-alist do not
694 ;; match the error messages when the language is not English.
695 ;; Hence we add a regexp.
696
697 (defconst caml-error-regexp
698   "^[A-\377]+ \"\\([^\"\n]+\\)\", [A-\377]+ \\([0-9]+\\)[-,:]"
699   "Regular expression matching the error messages produced by camlc.")
700
701 (if (boundp 'compilation-error-regexp-alist)
702     (or (assoc caml-error-regexp
703                compilation-error-regexp-alist)
704         (setq compilation-error-regexp-alist
705               (cons (list caml-error-regexp 1 2)
706                compilation-error-regexp-alist))))
707
708 ;; A regexp to extract the range info
709
710 (defconst caml-error-chars-regexp
711   ".*, .*, [A-\377]+ \\([0-9]+\\)-\\([0-9]+\\):"
712   "Regular expression extracting the character numbers
713 from an error message produced by camlc.")
714
715 ;; Wrapper around next-error.
716
717 (defvar caml-error-overlay nil)
718
719 ;;itz 04-21-96 somebody didn't get the documetation for next-error
720 ;;right. When the optional argument is a number n, it should move
721 ;;forward n errors, not reparse.
722
723 ;itz 04-21-96 instead of defining a new function, use defadvice
724 ;that way we get our effect even when we do \C-x` in compilation buffer
725
726 (defadvice next-error (after caml-next-error activate)
727  "Reads the extra positional information provided by the Caml compiler.
728
729 Puts the point and the mark exactly around the erroneous program
730 fragment. The erroneous fragment is also temporarily highlighted if
731 possible."
732
733  (if (eq major-mode 'caml-mode)
734      (let (bol beg end)
735        (save-excursion
736          (set-buffer
737           (if (boundp 'compilation-last-buffer)
738               compilation-last-buffer   ;Emacs 19
739             "*compilation*"))           ;Emacs 18
740          (save-excursion
741            (goto-char (window-point (get-buffer-window (current-buffer))))
742            (if (looking-at caml-error-chars-regexp)
743                (setq beg
744                      (string-to-int
745                       (buffer-substring (match-beginning 1) (match-end 1)))
746                      end
747                      (string-to-int
748                       (buffer-substring (match-beginning 2) (match-end 2)))))))
749        (cond (beg
750               (setq end (- end beg))
751               (beginning-of-line)
752               (forward-byte beg)
753               (setq beg (point))
754               (forward-byte end)
755               (setq end (point))
756               (goto-char beg)
757               (push-mark end t)
758               (cond ((fboundp 'make-overlay)
759                      (if caml-error-overlay ()
760                        (setq caml-error-overlay (make-overlay 1 1))
761                        (overlay-put caml-error-overlay 'face 'region))
762                      (unwind-protect
763                          (progn
764                            (move-overlay caml-error-overlay
765                                          beg end (current-buffer))
766                            (sit-for 60))
767                        (delete-overlay caml-error-overlay)))))))))
768
769 ;; Usual match-string doesn't work properly with font-lock-mode
770 ;; on some emacs.
771
772 (defun caml-match-string (num &optional string)
773
774   "Return string of text matched by last search, without properties.
775
776 NUM specifies which parenthesized expression in the last regexp.
777 Value is nil if NUMth pair didn't match, or there were less than NUM
778 pairs.  Zero means the entire text matched by the whole regexp or
779 whole string."
780
781   (let* ((data (match-data))
782          (begin (nth (* 2 num) data))
783          (end (nth (1+ (* 2 num)) data)))
784     (if string (substring string begin end)
785       (buffer-substring-no-properties begin end))))
786
787 ;; itz Thu Sep 24 19:02:42 PDT 1998 this is to have some level of
788 ;; comfort when sending phrases to the toplevel and getting errors.
789 (defun caml-goto-phrase-error ()
790   "Find the error location in current Caml phrase."
791   (interactive)
792   (require 'inf-caml)
793   (let ((bounds (save-excursion (caml-mark-phrase))))
794     (inferior-caml-goto-error (car bounds) (cdr bounds))))
795
796 ;;; Phrases
797
798 ;itz the heuristics used to see if we're `between two phrases'
799 ;didn't seem right to me.
800
801 (defconst caml-phrase-start-keywords
802   (concat "\\<\\(class\\|ex\\(ternal\\|ception\\)\\|functor"
803           "\\|let\\|module\\|open\\|type\\|val\\)\\>")
804   "Keywords starting phrases in files")
805
806 ;; a phrase starts when a toplevel keyword is at the beginning of a line
807 (defun caml-at-phrase-start-p ()
808   (and (bolp)
809        (or (looking-at "#")
810            (looking-at caml-phrase-start-keywords))))
811
812 (defun caml-skip-comments-forward ()
813   (skip-chars-forward " \n\t")
814   (while (or (looking-at comment-start-skip) (caml-in-comment-p))
815     (if (= (following-char) ?\)) (forward-char)
816       (search-forward comment-end))
817     (skip-chars-forward " \n\t")))
818
819 (defun caml-skip-comments-backward ()
820   (skip-chars-backward " \n\t")
821   (while (and (eq (preceding-char) ?\)) (eq (char-after (- (point) 2)) ?*))
822     (backward-char)
823     (while (caml-in-comment-p) (search-backward comment-start))
824     (skip-chars-backward " \n\t")))
825
826 (defconst caml-phrase-sep-keywords (concat ";;\\|" caml-phrase-start-keywords))
827
828 (defun caml-find-phrase (&optional min-pos max-pos)
829   "Find the CAML phrase containing the point.
830 Return the position of the beginning of the phrase, and move point
831 to the end.
832 "
833   (interactive)
834   (if (not min-pos) (setq min-pos (point-min)))
835   (if (not max-pos) (setq max-pos (point-max)))
836   (let (beg end use-semi kwop)
837     ;(caml-skip-comments-backward)
838     (cond
839      ; shall we have special processing for semicolons?
840      ;((and (eq (char-before (- (point) 1)) ?\;) (eq (char-before) ?\;))
841      ; (forward-char)
842      ; (caml-skip-comments-forward)
843      ; (setq beg (point))
844      ; (while (and (search-forward ";;" max-pos 'move)
845      ;    (or (caml-in-comment-p) (caml-in-literal-p)))))
846      (t
847       (caml-skip-comments-forward)
848       (if (caml-at-phrase-start-p) (forward-char))
849       (while (and (cond
850                    ((re-search-forward caml-phrase-sep-keywords max-pos 'move)
851                     (goto-char (match-beginning 0)) t))
852                   (or (not (or (bolp) (looking-at ";;")))
853                       (caml-in-comment-p)
854                       (caml-in-literal-p)))
855         (forward-char))
856       (setq end (+ (point) (if (looking-at ";;") 2 0)))
857       (while (and
858               (setq kwop (caml-find-kwop caml-phrase-sep-keywords min-pos))
859               (not (string= kwop ";;"))
860               (not (bolp))))
861       (if (string= kwop ";;") (forward-char 2))
862       (if (not kwop) (goto-char min-pos))
863       (caml-skip-comments-forward)
864       (setq beg (point))
865       (if (>= beg end) (error "no phrase before point"))
866       (goto-char end)))
867     (caml-skip-comments-forward)
868     beg))
869
870 (defun caml-mark-phrase (&optional min-pos max-pos)
871   "Put mark at end of this Caml phrase, point at beginning.
872 "
873   (interactive)
874   (let* ((beg (caml-find-phrase min-pos max-pos)) (end (point)))
875     (push-mark)
876     (goto-char beg)
877     (cons beg end)))
878     
879 ;;itz Fri Sep 25 12:58:13 PDT 1998 support for adding change-log entries
880 (defun caml-current-defun ()
881   (save-excursion
882     (caml-mark-phrase)
883     (if (not (looking-at caml-phrase-start-keywords)) nil
884       (re-search-forward caml-phrase-start-keywords)
885       (let ((done nil))
886         (while (not done)
887           (cond
888            ((looking-at "\\s ")
889             (skip-syntax-forward " "))
890            ((char-equal (following-char) ?\( )
891             (forward-sexp 1))
892            ((char-equal (following-char) ?')
893             (skip-syntax-forward "w_"))
894            (t (setq done t)))))
895       (re-search-forward "\\(\\sw\\|\\s_\\)+")
896       (match-string 0))))
897
898 (defun caml-overlap (b1 e1 b2 e2)
899   (<= (max b1 b2) (min e1 e2)))
900
901 ;this clears the last comment cache if necessary
902 (defun caml-before-change-function (begin end)
903   (if (and caml-last-noncomment-pos
904            (> caml-last-noncomment-pos begin))
905       (setq caml-last-noncomment-pos nil))
906   (if (and (marker-position caml-last-comment-start)
907            (marker-position caml-last-comment-end)
908            (caml-overlap begin end
909                          caml-last-comment-start
910                          caml-last-comment-end))
911       (prog2
912           (set-marker caml-last-comment-start nil)
913           (set-marker caml-last-comment-end nil)))
914   (let ((orig-function (default-value 'before-change-function)))
915     (if orig-function (funcall orig-function begin end))))
916
917 (defun caml-in-literal-p ()
918   "Returns non-nil if point is inside a caml literal."
919   (let* ((start-literal (concat "[\"" caml-quote-char "]"))
920          (char-literal
921           (concat "\\([^\\]\\|\\\\\\.\\|\\\\[0-9][0-9][0-9]\\)"
922                   caml-quote-char))
923          (pos (point))
924          (eol (progn (end-of-line 1) (point)))
925          state in-str)
926     (beginning-of-line 1)
927     (while (and (not state)
928                 (re-search-forward start-literal eol t)
929                 (<= (point) pos))
930       (cond
931        ((string= (caml-match-string 0) "\"")
932         (setq in-str t)
933         (while (and in-str (not state)
934                     (re-search-forward "\"\\|\\\\\"" eol t))
935           (if (> (point) pos) (setq state t))
936           (if (string= (caml-match-string 0) "\"") (setq in-str nil)))
937         (if in-str (setq state t)))
938        ((looking-at char-literal)
939         (if (and (>= pos (match-beginning 0)) (< pos (match-end 0)))
940             (setq state t)
941           (goto-char (match-end 0))))))
942     (goto-char pos)
943     state))
944
945 (defun caml-forward-comment ()
946   "Skip one (eventually nested) comment."
947   (let ((count 1) match)
948     (while (> count 0)
949       (if (not (re-search-forward "(\\*\\|\\*)" nil 'move))
950           (setq count -1)
951         (setq match (caml-match-string 0))
952         (cond
953          ((caml-in-literal-p)
954           nil)
955          ((string= match comment-start)
956           (setq count (1+ count)))
957          (t
958           (setq count (1- count))))))
959     (= count 0)))
960
961 (defun caml-backward-comment ()
962   "Skip one (eventually nested) comment."
963   (let ((count 1) match)
964     (while (> count 0)
965       (if (not (re-search-backward "(\\*\\|\\*)" nil 'move))
966           (setq count -1)
967         (setq match (caml-match-string 0))
968         (cond
969          ((caml-in-literal-p)
970           nil)
971          ((string= match comment-start)
972           (setq count (1- count)))
973          (t
974           (setq count (1+ count))))))
975     (= count 0)))
976
977 (defun caml-in-comment-p ()
978   "Returns non-nil if point is inside a caml comment.
979 Returns nil for the parenthesis openning a comment."
980   ;;we look for comments differently than literals. there are two
981   ;;reasons for this. first, caml has nested comments and it is not so
982   ;;clear that parse-partial-sexp supports them; second, if proper
983   ;;style is used, literals are never split across lines, so we don't
984   ;;have to worry about bogus phrase breaks inside literals, while we
985   ;;have to account for that possibility in comments.
986   (save-excursion
987     (let* ((cached-pos caml-last-noncomment-pos)
988            (cached-begin (marker-position caml-last-comment-start))
989            (cached-end (marker-position caml-last-comment-end)))
990       (cond
991        ((and cached-begin cached-end
992              (< cached-begin (point)) (< (point) cached-end)) t)
993        ((and cached-pos (= cached-pos (point))) nil)
994        ((and cached-pos (> cached-pos (point))
995              (< (abs (- cached-pos (point))) caml-lookback-limit))
996         (let (end found (here (point)))
997           ; go back to somewhere sure
998           (goto-char cached-pos)
999           (while (> (point) here)
1000             ; look for the end of a comment
1001             (while (and (if (search-backward comment-end (1- here) 'move)
1002                             (setq end (match-end 0))
1003                           (setq end nil))
1004                         (caml-in-literal-p)))
1005             (if end (setq found (caml-backward-comment))))
1006           (if (and found (= (point) here)) (setq end nil))
1007           (if (not end)
1008               (setq caml-last-noncomment-pos here)
1009             (set-marker caml-last-comment-start (point))
1010             (set-marker caml-last-comment-end end))
1011           end))
1012        (t
1013         (let (begin found (here (point)))
1014           ; go back to somewhere sure (or far enough)
1015           (goto-char
1016            (if cached-pos cached-pos (- (point) caml-lookback-limit)))
1017           (while (< (point) here)
1018             ; look for the beginning of a comment
1019             (while (and (if (search-forward comment-start (1+ here) 'move)
1020                             (setq begin (match-beginning 0))
1021                           (setq begin nil))
1022                         (caml-in-literal-p)))
1023             (if begin (setq found (caml-forward-comment))))
1024           (if (and found (= (point) here)) (setq begin nil))
1025           (if (not begin)
1026               (setq caml-last-noncomment-pos here)
1027             (set-marker caml-last-comment-start begin)
1028             (set-marker caml-last-comment-end (point)))
1029           begin))))))
1030
1031 ;; Various constants and regexps
1032
1033 (defconst caml-before-expr-prefix
1034   (concat "\\<\\(asr\\|begin\\|class\\|do\\(wnto\\)?\\|else"
1035           "\\|i\\(f\\|n\\(herit\\|itializer\\)?\\)"
1036           "\\|f\\(or\\|un\\(ct\\(ion\\|or\\)\\)?\\)"
1037           "\\|l\\(and\\|or\\|s[lr]\\|xor\\)\\|m\\(atch\\|od\\)"
1038           "\\|o[fr]\\|parser\\|s\\(ig\\|truct\\)\\|t\\(hen\\|o\\|ry\\)"
1039           "\\|w\\(h\\(en\\|ile\\)\\|ith\\)\\)\\>\\|:begin\\>"
1040           "\\|[=<>@^|&+-*/$%][!$%*+-./:<=>?@^|~]*\\|:[:=]\\|[[({,;]")
1041
1042   "Keywords that may appear immediately before an expression.
1043 Used to distinguish it from toplevel let construct.")
1044
1045 (defconst caml-matching-kw-regexp
1046   (concat
1047    "\\<\\(and\\|do\\(ne\\)?\\|e\\(lse\\|nd\\)\\|in\\|t\\(hen\\|o\\)"
1048    "\\|with\\)\\>\\|[^[|]|")
1049   "Regexp used in caml mode for skipping back over nested blocks.")
1050
1051 (defconst caml-matching-kw-alist
1052   '(("|" . caml-find-pipe-match)
1053     (";" . caml-find-semi-match)
1054     ("," . caml-find-comma-match)
1055     ("end" . caml-find-end-match)
1056     ("done" . caml-find-done-match)
1057     ("in"  . caml-find-in-match)
1058     ("with" . caml-find-with-match)
1059     ("else" . caml-find-else-match)
1060     ("then" . caml-find-then-match)
1061     ("to" . caml-find-done-match)
1062     ("do" . caml-find-done-match)
1063     ("and" . caml-find-and-match))
1064
1065   "Association list used in caml mode for skipping back over nested blocks.")
1066
1067 (defconst caml-kwop-regexps (make-vector 9 nil)
1068   "Array of regexps representing caml keywords of different priorities.")
1069
1070 (defun caml-in-expr-p ()
1071   (let ((pos (point)) (in-expr t))
1072     (caml-find-kwop
1073      (concat caml-before-expr-prefix "\\|"
1074              caml-matching-kw-regexp "\\|"
1075              (aref caml-kwop-regexps caml-max-indent-priority)))
1076     (cond
1077      ; special case for ;;
1078      ((and (> (point) 1) (= (preceding-char) ?\;) (= (following-char) ?\;))
1079       (setq in-expr nil))
1080      ((looking-at caml-before-expr-prefix)
1081       (if (not (looking-at "(\\*")) (goto-char (match-end 0)))
1082       (skip-chars-forward " \t\n")
1083       (while (looking-at "(\\*")
1084         (forward-char)
1085         (caml-forward-comment)
1086         (skip-chars-forward " \t\n"))
1087       (if (<= pos (point)) (setq in-expr nil))))
1088     (goto-char pos)
1089     in-expr))
1090
1091 (defun caml-at-sexp-close-p ()
1092   (or (char-equal ?\) (following-char))
1093       (char-equal ?\] (following-char))
1094       (char-equal ?} (following-char))))
1095
1096 (defun caml-find-kwop (kwop-regexp &optional min-pos)
1097   "Look back for a caml keyword or operator matching KWOP-REGEXP.
1098 Second optional argument MIN-POS bounds the search.
1099
1100 Ignore occurences inside literals. If found, return a list of two
1101 values: the actual text of the keyword or operator, and a boolean
1102 indicating whether the keyword was one we looked for explicitly
1103 {non-nil}, or on the other hand one of the block-terminating
1104 keywords."
1105
1106   (let ((start-literal (concat "[\"" caml-quote-char "]"))
1107         found kwop)
1108     (while (and (> (point) 1) (not found)
1109                 (re-search-backward kwop-regexp min-pos 'move))
1110       (setq kwop (caml-match-string 0))
1111       (cond
1112        ((looking-at "(\\*")
1113         (if (> (point) 1) (backward-char)))
1114        ((caml-in-comment-p)
1115         (search-backward "(" min-pos 'move))
1116        ((looking-at start-literal))
1117        ((caml-in-literal-p)
1118         (re-search-backward start-literal min-pos 'move))  ;ugly hack
1119        ((setq found t))))
1120     (if found
1121         (if (not (string-match "\\`[^|[]|[^]|]?\\'" kwop)) ;arrrrgh!!
1122             kwop
1123           (forward-char 1) "|") nil)))
1124
1125 ;  Association list of indentation values based on governing keywords.
1126 ;
1127 ;Each element is of the form (KEYWORD OP-TYPE PRIO INDENT). OP-TYPE is
1128 ;non-nil for operator-type nodes, which affect indentation in a
1129 ;different way from keywords: subsequent lines are indented to the
1130 ;actual occurrence of an operator, but relative to the indentation of
1131 ;the line where the governing keyword occurs.
1132
1133 (defconst caml-no-indent 0)
1134
1135 (defconst caml-kwop-alist
1136   '(("begin"            nil     6       caml-begin-indent)
1137     (":begin"           nil     6       caml-begin-indent) ; hack
1138     ("class"            nil     0       caml-class-indent)
1139     ("constraint"       nil     0       caml-val-indent)
1140     ("sig"              nil     1       caml-sig-indent)
1141     ("struct"           nil     1       caml-struct-indent)
1142     ("exception"        nil     0       caml-exception-indent)
1143     ("for"              nil     6       caml-for-indent)
1144     ("fun"              nil     3       caml-fun-indent)
1145     ("function"         nil     3       caml-function-indent)
1146     ("if"               nil     6       caml-if-indent)
1147     ("if-else"          nil     6       caml-if-else-indent)
1148     ("include"          nil     0       caml-include-indent)
1149     ("inherit"          nil     0       caml-inherit-indent)
1150     ("initializer"      nil     0       caml-initializer-indent)
1151     ("let"              nil     6       caml-let-indent)
1152     ("let-in"           nil     6       caml-let-in-indent)
1153     ("match"            nil     6       caml-match-indent)
1154     ("method"           nil     0       caml-method-indent)
1155     ("module"           nil     0       caml-module-indent)
1156     ("object"           nil     6       caml-object-indent)
1157     ("of"               nil     7       caml-of-indent)
1158     ("open"             nil     0       caml-no-indent)
1159     ("parser"           nil     3       caml-parser-indent)
1160     ("try"              nil     6       caml-try-indent)
1161     ("type"             nil     0       caml-type-indent)
1162     ("val"              nil     0       caml-val-indent)
1163     ("when"             nil     2       caml-if-indent)
1164     ("while"            nil     6       caml-while-indent)
1165     ("::"               t       5       caml-::-indent)
1166     ("@"                t       4       caml-@-indent)
1167     ("^"                t       4       caml-@-indent)
1168     (":="               nil     3       caml-:=-indent)
1169     ("<-"               nil     3       caml-<--indent)
1170     ("->"               nil     2       caml-->-indent)
1171     ("\["               t       8       caml-lb-indent)
1172     ("{"                t       8       caml-lc-indent)
1173     ("\("               t       8       caml-lp-indent)
1174     ("|"                nil     2       caml-no-indent)
1175     (";;"               nil     0       caml-no-indent))
1176 ; if-else and let-in are not keywords but idioms
1177 ; "|" is not in the regexps
1178 ; all these 3 values correspond to hard-coded names
1179
1180 "Association list of indentation values based on governing keywords.
1181
1182 Each element is of the form (KEYWORD OP-TYPE PRIO INDENT). OP-TYPE is
1183 non-nil for operator-type nodes, which affect indentation in a
1184 different way from keywords: subsequent lines are indented to the
1185 actual occurrence of an operator, but relative to the indentation of
1186 the line where the governing keyword occurs.")
1187
1188 ;;Originally, we had caml-kwop-regexp create these at runtime, from an
1189 ;;additional field in caml-kwop-alist. That proved way too slow,
1190 ;;although I still can't understand why. itz
1191
1192 (aset caml-kwop-regexps 0
1193       (concat
1194        "\\<\\(begin\\|object\\|for\\|s\\(ig\\|truct\\)\\|while\\)\\>"
1195        "\\|:begin\\>\\|[[({]\\|;;"))
1196 (aset caml-kwop-regexps 1
1197       (concat (aref caml-kwop-regexps 0) "\\|\\<\\(class\\|module\\)\\>"))
1198 (aset caml-kwop-regexps 2
1199       (concat
1200        (aref caml-kwop-regexps 1)
1201        "\\|\\<\\(fun\\(ction\\)?\\|initializer\\|let\\|m\\(atch\\|ethod\\)"
1202        "\\|parser\\|try\\|val\\)\\>\\|->"))
1203 (aset caml-kwop-regexps 3
1204       (concat (aref caml-kwop-regexps 2) "\\|\\<if\\|when\\>"))
1205 (aset caml-kwop-regexps 4
1206       (concat (aref caml-kwop-regexps 3) "\\|:=\\|<-"))
1207 (aset caml-kwop-regexps 5
1208       (concat (aref caml-kwop-regexps 4) "\\|@"))
1209 (aset caml-kwop-regexps 6
1210       (concat (aref caml-kwop-regexps 5) "\\|::\\|\\^"))
1211 (aset caml-kwop-regexps 7
1212       (concat
1213        (aref caml-kwop-regexps 0)
1214        "\\|\\<\\(constraint\\|exception\\|in\\(herit\\|clude\\)"
1215        "\\|o\\(f\\|pen\\)\\|type\\|val\\)\\>"))
1216 (aset caml-kwop-regexps 8
1217       (concat (aref caml-kwop-regexps 6)
1218        "\\|\\<\\(constraint\\|exception\\|in\\(herit\\|clude\\)"
1219        "\\|o\\(f\\|pen\\)\\|type\\)\\>"))
1220
1221 (defun caml-find-done-match ()
1222   (let ((unbalanced 1) (kwop t))
1223     (while (and (not (= 0 unbalanced)) kwop)
1224       (setq kwop (caml-find-kwop "\\<\\(done\\|for\\|while\\)\\>"))
1225       (cond
1226        ((not kwop))
1227        ((string= kwop "done") (setq unbalanced (1+ unbalanced)))
1228        (t (setq unbalanced (1- unbalanced)))))
1229     kwop))
1230
1231 (defun caml-find-end-match ()
1232   (let ((unbalanced 1) (kwop t))
1233     (while (and (not (= 0 unbalanced)) kwop)
1234       (setq kwop
1235             (caml-find-kwop
1236              "\\<\\(end\\|begin\\|object\\|s\\(ig\\|truct\\)\\)\\>\\|:begin\\>\\|;;"))
1237       (cond
1238        ((not kwop))
1239        ((string= kwop ";;") (setq kwop nil) (forward-line 1))
1240        ((string= kwop "end") (setq unbalanced (1+ unbalanced)))
1241        ( t (setq unbalanced (1- unbalanced)))))
1242     (if (string= kwop ":begin") "begin"
1243       kwop)))
1244
1245 (defun caml-find-in-match ()
1246   (let ((unbalanced 1) (kwop t))
1247     (while (and (not (= 0 unbalanced)) kwop)
1248       (setq kwop (caml-find-kwop "\\<\\(in\\|let\\|end\\)\\>"))
1249       (cond
1250        ((not kwop))
1251        ((string= kwop "end") (caml-find-end-match))
1252        ((string= kwop "in") (setq unbalanced (1+ unbalanced)))
1253        (t (setq unbalanced (1- unbalanced)))))
1254     kwop))
1255
1256 (defun caml-find-with-match ()
1257   (let ((unbalanced 1) (kwop t))
1258     (while (and (not (= 0 unbalanced)) kwop)
1259       (setq kwop
1260             (caml-find-kwop
1261              "\\<\\(with\\|try\\|m\\(atch\\|odule\\)\\|functor\\)\\>\\|{\\|}"))
1262       (cond
1263        ((not kwop))
1264        ((or (string= kwop "module") (string= kwop "functor"))
1265         (setq unbalanced 0))
1266        ((or (string= kwop "with") (string= kwop "}"))
1267         (setq unbalanced (1+ unbalanced)))
1268        (t (setq unbalanced (1- unbalanced)))))
1269     kwop))
1270
1271 (defun caml-find-paren-match (close)
1272   (let ((unbalanced 1)
1273         (regexp (cond ((= close ?\)) "[()]")
1274                       ((= close ?\]) "[][]")
1275                       ((= close ?\}) "[{}]"))))
1276     (while (and (> unbalanced 0)
1277                 (caml-find-kwop regexp))
1278       (if (= close (following-char))
1279           (setq unbalanced (1+ unbalanced))
1280         (setq unbalanced (1- unbalanced))))))
1281
1282 (defun caml-find-then-match (&optional from-else)
1283   (let ((bol (if from-else
1284                  (save-excursion
1285                    (progn (beginning-of-line) (point)))))
1286         kwop done matching-fun)
1287     (while (not done)
1288       (setq kwop
1289             (caml-find-kwop
1290              "\\<\\(e\\(nd\\|lse\\)\\|done\\|then\\|if\\|with\\)\\>\\|[])};]"))
1291       (cond
1292        ((not kwop) (setq done t))
1293        ((caml-at-sexp-close-p)
1294         (caml-find-paren-match (following-char)))
1295        ((string= kwop "if") (setq done t))
1296        ((string= kwop "then")
1297         (if (not from-else) (setq kwop (caml-find-then-match))))
1298        ((setq matching-fun (cdr-safe (assoc kwop caml-matching-kw-alist)))
1299         (setq kwop (funcall matching-fun)))))
1300     (if (and bol (>= (point) bol))
1301         "if-else"
1302       kwop)))
1303
1304 (defun caml-find-pipe-match ()
1305   (let ((done nil) (kwop)
1306         (re (concat
1307              "\\<\\(try\\|match\\|with\\|function\\|parser\\|type"
1308              "\\|e\\(nd\\|lse\\)\\|done\\|then\\|in\\)\\>"
1309              "\\|[^[|]|\\|[])}]")))
1310     (while (not done)
1311       (setq kwop (caml-find-kwop re))
1312       (cond
1313        ((not kwop) (setq done t))
1314        ((looking-at "[^[|]\\(|\\)")
1315         (goto-char (match-beginning 1))
1316         (setq kwop "|")
1317         (setq done t))
1318        ((caml-at-sexp-close-p)
1319         (caml-find-paren-match (following-char)))
1320        ((string= kwop "with")
1321         (setq kwop (caml-find-with-match))
1322         (setq done t))
1323        ((string= kwop "parser")
1324         (if (re-search-backward "\\<with\\>" (- (point) 5) t)
1325             (setq kwop (caml-find-with-match)))
1326         (setq done t))
1327        ((string= kwop "done") (caml-find-done-match))
1328        ((string= kwop "end") (caml-find-end-match))
1329        ((string= kwop "then") (caml-find-then-match))
1330        ((string= kwop "else") (caml-find-else-match))
1331        ((string= kwop "in") (caml-find-in-match))
1332        (t (setq done t))))
1333     kwop))
1334
1335 (defun caml-find-and-match ()
1336   (let ((done nil) (kwop))
1337     (while (not done)
1338       (setq kwop (caml-find-kwop
1339                   "\\<\\(object\\|exception\\|let\\|type\\|end\\|in\\)\\>"))
1340       (cond
1341        ((not kwop) (setq done t))
1342        ((string= kwop "end") (caml-find-end-match))
1343        ((string= kwop "in") (caml-find-in-match))
1344        (t (setq done t))))
1345     kwop))
1346
1347 (defun caml-find-else-match ()
1348   (caml-find-then-match t))
1349
1350 (defun caml-find-semi-match ()
1351   (caml-find-kwop-skipping-blocks 2))
1352
1353 (defun caml-find-comma-match ()
1354   (caml-find-kwop-skipping-blocks 3))
1355
1356 (defun caml-find-kwop-skipping-blocks (prio)
1357   "Look back for a caml keyword matching caml-kwop-regexps [PRIO].
1358
1359  Skip nested blocks."
1360
1361   (let ((done nil) (kwop nil) (matching-fun)
1362         (kwop-list (aref caml-kwop-regexps prio)))
1363     (while (not done)
1364       (setq kwop (caml-find-kwop
1365                   (concat caml-matching-kw-regexp
1366                           (cond ((> prio 3) "\\|[])},;]\\|")
1367                                 ((> prio 2) "\\|[])};]\\|")
1368                                 (t "\\|[])}]\\|"))
1369                           kwop-list)))
1370       (cond
1371        ((not kwop) (setq done t))
1372        ((caml-at-sexp-close-p)
1373         (caml-find-paren-match (following-char)))
1374        ((or (string= kwop ";;")
1375             (and (string= kwop ";") (= (preceding-char) ?\;)))
1376         (forward-line 1)
1377         (setq kwop ";;")
1378         (setq done t))
1379        ((and (>= prio 2) (string= kwop "|")) (setq done t))
1380        ((string= kwop "end") (caml-find-end-match))
1381        ((string= kwop "done") (caml-find-done-match))
1382        ((string= kwop "in")
1383         (cond ((and (caml-find-in-match) (>= prio 2))
1384                (setq kwop "let-in")
1385                (setq done t))))
1386        ((and (string= kwop "parser") (>= prio 2)
1387              (re-search-backward "\\<with\\>" (- (point) 5) t))
1388         (setq kwop (caml-find-with-match))
1389         (setq done t))
1390        ((setq matching-fun (cdr-safe (assoc kwop caml-matching-kw-alist)))
1391         (setq kwop (funcall matching-fun))
1392         (if (looking-at kwop-list) (setq done t)))
1393        (t (let* ((kwop-info (assoc kwop caml-kwop-alist))
1394                  (is-op (and (nth 1 kwop-info)
1395                              ; check that we are not at beginning of line
1396                              (let ((pos (point)) bti)
1397                                (back-to-indentation)
1398                                (setq bti (point))
1399                                (goto-char pos)
1400                                (< bti pos)))))
1401             (if (and is-op (looking-at
1402                             (concat (regexp-quote kwop)
1403                                     "|?[ \t]*\\(\n\\|(\\*\\)")))
1404                 (setq kwop-list
1405                       (aref caml-kwop-regexps (nth 2 kwop-info)))
1406               (setq done t))))))
1407     kwop))
1408
1409 (defun caml-compute-basic-indent (prio)
1410   "Compute indent of current caml line, ignoring leading keywords.
1411
1412 Find the `governing node' for current line. Compute desired
1413 indentation based on the node and the indentation alists.
1414 Assumes point is exactly at line indentation.
1415 Does not preserve point."
1416
1417   (let* (in-expr
1418          (kwop (cond
1419                 ((looking-at ";;")
1420                  (beginning-of-line 1))
1421                 ((looking-at "|\\([^]|]\\|\\'\\)")
1422                  (caml-find-pipe-match))
1423                 ((and (looking-at caml-phrase-start-keywords)
1424                       (caml-in-expr-p))
1425                  (caml-find-end-match))
1426                 ((and (looking-at caml-matching-kw-regexp)
1427                       (assoc (caml-match-string 0) caml-matching-kw-alist))
1428                  (funcall (cdr-safe (assoc (caml-match-string 0)
1429                                       caml-matching-kw-alist))))
1430                 ((looking-at
1431                   (aref caml-kwop-regexps caml-max-indent-priority))
1432                  (let* ((kwop (caml-match-string 0))
1433                         (kwop-info (assoc kwop caml-kwop-alist))
1434                         (prio (if kwop-info (nth 2 kwop-info)
1435                                 caml-max-indent-priority)))
1436                    (if (and (looking-at (aref caml-kwop-regexps 0))
1437                             (not (looking-at "object"))
1438                             (caml-in-expr-p))
1439                        (setq in-expr t))
1440                    (caml-find-kwop-skipping-blocks prio)))
1441                 (t
1442                  (if (and (= prio caml-max-indent-priority) (caml-in-expr-p))
1443                      (setq in-expr t))
1444                  (caml-find-kwop-skipping-blocks prio))))
1445          (kwop-info (assoc kwop caml-kwop-alist))
1446          (indent-diff
1447           (cond
1448            ((not kwop-info) (beginning-of-line 1) 0)
1449            ((looking-at "[[({][|<]?[ \t]*")
1450             (length (caml-match-string 0)))
1451            ((nth 1 kwop-info) (symbol-value (nth 3 kwop-info)))
1452            (t
1453             (let ((pos (point)))
1454               (back-to-indentation)
1455 ;             (if (looking-at "\\<let\\>") (goto-char pos))
1456               (- (symbol-value (nth 3 kwop-info))
1457                  (if (looking-at "|") caml-|-extra-indent 0))))))
1458          (extra (if in-expr caml-apply-extra-indent 0)))
1459          (+ indent-diff extra (current-column))))
1460
1461 (defconst caml-leading-kwops-regexp
1462   (concat
1463    "\\<\\(and\\|do\\(ne\\)?\\|e\\(lse\\|nd\\)\\|in"
1464    "\\|t\\(hen\\|o\\)\\|with\\)\\>\\|[]|})]")
1465
1466   "Regexp matching caml keywords which need special indentation.")
1467
1468 (defconst caml-leading-kwops-alist
1469   '(("and" caml-and-extra-indent 2)
1470     ("do" caml-do-extra-indent 0)
1471     ("done" caml-done-extra-indent 0)
1472     ("else" caml-else-extra-indent 3)
1473     ("end" caml-end-extra-indent 0)
1474     ("in" caml-in-extra-indent 2)
1475     ("then" caml-then-extra-indent 3)
1476     ("to" caml-to-extra-indent 0)
1477     ("with" caml-with-extra-indent 2)
1478     ("|" caml-|-extra-indent 2)
1479     ("]" caml-rb-extra-indent 0)
1480     ("}" caml-rc-extra-indent 0)
1481     (")" caml-rp-extra-indent 0))
1482
1483   "Association list of special caml keyword indent values.
1484
1485 Each member is of the form (KEYWORD EXTRA-INDENT PRIO) where
1486 EXTRA-INDENT is the variable holding extra indentation amount for
1487 KEYWORD (usually negative) and PRIO is upper bound on priority of
1488 matching nodes to determine KEYWORD's final indentation.")
1489
1490 (defun caml-compute-final-indent ()
1491   (save-excursion
1492     (back-to-indentation)
1493     (cond
1494      ((and (bolp) (looking-at comment-start-skip)) (current-column))
1495      ((caml-in-comment-p)
1496       (let ((closing (looking-at "\\*)"))
1497             (comment-mark (looking-at "\\*")))
1498         (caml-backward-comment)
1499         (looking-at comment-start-skip)
1500         (+ (current-column)
1501            (cond
1502             (closing 1)
1503             (comment-mark 1)
1504             (t caml-comment-indent)))))
1505      (t (let* ((leading (looking-at caml-leading-kwops-regexp))
1506                (assoc-val (if leading (assoc (caml-match-string 0)
1507                                              caml-leading-kwops-alist)))
1508                (extra (if leading (symbol-value (nth 1 assoc-val)) 0))
1509                (prio (if leading (nth 2 assoc-val)
1510                        caml-max-indent-priority))
1511                (basic (caml-compute-basic-indent prio)))
1512           (max 0 (if extra (+ extra basic) (current-column))))))))
1513
1514
1515
1516 (defun caml-split-string ()
1517   "Called whenever a line is broken inside a caml string literal."
1518   (insert-before-markers "\"^\"")
1519   (backward-char 1))
1520
1521 (defadvice indent-new-comment-line (around
1522                                     caml-indent-new-comment-line
1523                                     activate)
1524
1525   "Handle multi-line strings in caml mode."
1526
1527 ;this advice doesn't make sense in other modes. I wish there were a
1528 ;cleaner way to do this: I haven't found one.
1529
1530   (let ((hooked (and (eq major-mode 'caml-mode) (caml-in-literal-p)))
1531         (split-mark))
1532     (if (not hooked) nil
1533       (setq split-mark (set-marker (make-marker) (point)))
1534       (caml-split-string))
1535     ad-do-it
1536     (if (not hooked) nil
1537       (goto-char split-mark)
1538       (set-marker split-mark nil))))
1539
1540 (defadvice newline-and-indent (around
1541                                caml-newline-and-indent
1542                                activate)
1543
1544   "Handle multi-line strings in caml mode."
1545
1546     (let ((hooked (and (eq major-mode 'caml-mode) (caml-in-literal-p)))
1547         (split-mark))
1548     (if (not hooked) nil
1549       (setq split-mark (set-marker (make-marker) (point)))
1550       (caml-split-string))
1551     ad-do-it
1552     (if (not hooked) nil
1553       (goto-char split-mark)
1554       (set-marker split-mark nil))))
1555
1556 (defun caml-electric-pipe ()
1557   "If inserting a | or } operator at beginning of line, reindent the line.
1558
1559 Unfortunately there is a situation where this mechanism gets
1560 confused. It's when | is the first character of a |] sequence. This is
1561 a misfeature of caml syntax and cannot be fixed, however, as a
1562 workaround, the electric ] inserts | itself if the matching [ is
1563 followed by |."
1564
1565   (interactive "*")
1566   (let ((electric (and caml-electric-indent
1567                        (caml-in-indentation)
1568                        (not (caml-in-comment-p)))))
1569     (self-insert-command 1)
1570     (if electric (save-excursion (caml-indent-command)))))
1571
1572 (defun caml-electric-rb ()
1573   "If inserting a ] operator at beginning of line, reindent the line.
1574
1575 Also, if the matching [ is followed by a | and this ] is not preceded
1576 by |, insert one."
1577
1578   (interactive "*")
1579   (let* ((prec (preceding-char))
1580          (use-pipe (and caml-electric-close-vector
1581                         (not (caml-in-comment-p))
1582                         (not (caml-in-literal-p))
1583                         (or (not (numberp prec))
1584                             (not (char-equal ?| prec)))))
1585          (electric (and caml-electric-indent
1586                         (caml-in-indentation)
1587                         (not (caml-in-comment-p)))))
1588     (self-insert-command 1)
1589     (if electric (save-excursion (caml-indent-command)))
1590     (if (and use-pipe
1591              (save-excursion
1592                (condition-case nil
1593                    (prog2
1594                        (backward-list 1)
1595                        (looking-at "\\[|"))
1596                  (error ""))))
1597         (save-excursion
1598           (backward-char 1)
1599           (insert "|")))))
1600
1601 (defun caml-abbrev-hook ()
1602   "If inserting a leading keyword at beginning of line, reindent the line."
1603   ;itz unfortunately we need a special case
1604   (if (and (not (caml-in-comment-p)) (not (= last-command-char ?_)))
1605       (let* ((bol (save-excursion (beginning-of-line) (point)))
1606              (kw (save-excursion
1607                    (and (re-search-backward "^[ \t]*\\(\\sw+\\)\\=" bol t)
1608                         (caml-match-string 1)))))
1609         (if kw
1610             (let ((indent (save-excursion
1611                             (goto-char (match-beginning 1))
1612                             (caml-indent-command)
1613                             (current-column)))
1614                   (abbrev-correct (if (= last-command-char ?\ ) 1 0)))
1615               (indent-to (- indent
1616                             (or
1617                              (symbol-value
1618                               (nth 1
1619                                    (assoc kw caml-leading-kwops-alist)))
1620                              0)
1621                             abbrev-correct)))))))
1622
1623 ; (defun caml-indent-phrase ()
1624 ;   (interactive "*")
1625 ;   (let ((bounds (caml-mark-phrase)))
1626 ;     (indent-region (car bounds) (cdr bounds) nil)))
1627
1628 ;;; Additional commands by Didier to report errors in toplevel mode
1629
1630 (defun caml-skip-blank-forward ()
1631   (if (looking-at "[ \t\n]*\\((\\*\\([^*]\\|[^(]\\*[^)]\\)*\\*)[ \t\n]*\\)*")
1632       (goto-char (match-end 0))))
1633
1634 ;; to mark phrases, so that repeated calls will take several of them
1635 ;; knows little about Ocaml appart literals and comments, so it should work
1636 ;; with other dialects as long as ;; marks the end of phrase. 
1637
1638 (defun caml-indent-phrase (arg)
1639   "Indent current phrase
1640 with prefix arg, indent that many phrases starting with the current phrase."
1641   (interactive "p")
1642   (save-excursion
1643     (let ((beg (caml-find-phrase)))
1644     (while (progn (setq arg (- arg 1)) (> arg 0)) (caml-find-phrase))
1645     (indent-region beg (point) nil))))
1646
1647 (defun caml-indent-buffer ()
1648   (interactive)
1649   (indent-region (point-min) (point-max) nil))
1650
1651 (defun caml-backward-to-less-indent (&optional n)
1652   "Move cursor back  N lines with less or same indentation."
1653   (interactive "p")
1654   (beginning-of-line 1)
1655   (if (< n 0) (caml-forward-to-less-indent (- n))
1656     (while (> n 0)
1657       (let ((i (current-indentation)))
1658         (forward-line -1)
1659         (while (or (> (current-indentation) i)
1660                    (caml-in-comment-p)
1661                    (looking-at
1662                     (concat "[ \t]*\\(\n\\|" comment-start-skip "\\)")))
1663           (forward-line -1)))
1664       (setq n (1- n))))
1665   (back-to-indentation))
1666
1667 (defun caml-forward-to-less-indent (&optional n)
1668   "Move cursor back N lines with less or same indentation."
1669   (interactive "p")
1670   (beginning-of-line 1)
1671   (if (< n 0) (caml-backward-to-less-indent (- n))
1672     (while (> n 0)
1673       (let ((i (current-indentation)))
1674         (forward-line 1)
1675         (while (or (> (current-indentation) i)
1676                    (caml-in-comment-p)
1677                    (looking-at
1678                     (concat "[ \t]*\\(\n\\|" comment-start-skip "\\)")))
1679           (forward-line 1)))
1680       (setq n (1- n))))
1681   (back-to-indentation))
1682
1683 (defun caml-insert-begin-form ()
1684   "Inserts a nicely formatted begin-end form, leaving a mark after end."
1685   (interactive "*")
1686   (let ((prec (preceding-char)))
1687     (if (and (numberp prec) (not (char-equal ?\  (char-syntax prec))))
1688         (insert " ")))
1689   (let* ((c (current-indentation)) (i (+ caml-begin-indent c)))
1690     (insert "begin\n\nend")
1691     (push-mark)
1692     (indent-line-to c)
1693     (forward-line -1)
1694     (indent-line-to i)))
1695
1696 (defun caml-insert-for-form ()
1697   "Inserts a nicely formatted for-do-done form, leaving a mark after do(ne)."
1698   (interactive "*")
1699   (let ((prec (preceding-char)))
1700     (if (and (numberp prec) (not (char-equal ?\  (char-syntax prec))))
1701         (insert " ")))
1702   (let* ((c (current-indentation)) (i (+ caml-for-indent c)))
1703     (insert "for  do\n\ndone")
1704     (push-mark)
1705     (indent-line-to c)
1706     (forward-line -1)
1707     (indent-line-to i)
1708     (push-mark)
1709     (beginning-of-line 1)
1710     (backward-char 4)))
1711
1712 (defun caml-insert-if-form ()
1713   "Insert nicely formatted if-then-else form leaving mark after then, else."
1714   (interactive "*")
1715   (let ((prec (preceding-char)))
1716     (if (and (numberp prec) (not (char-equal ?\  (char-syntax prec))))
1717         (insert " ")))
1718   (let* ((c (current-indentation)) (i (+ caml-if-indent c)))
1719     (insert "if\n\nthen\n\nelse\n")
1720     (indent-line-to i)
1721     (push-mark)
1722     (forward-line -1)
1723     (indent-line-to c)
1724     (forward-line -1)
1725     (indent-line-to i)
1726     (push-mark)
1727     (forward-line -1)
1728     (indent-line-to c)
1729     (forward-line -1)
1730     (indent-line-to i)))
1731
1732 (defun caml-insert-match-form ()
1733   "Insert nicely formatted match-with form leaving mark after with."
1734   (interactive "*")
1735   (let ((prec (preceding-char)))
1736     (if (and (numberp prec) (not (char-equal ?\  (char-syntax prec))))
1737         (insert " ")))
1738   (let* ((c (current-indentation)) (i (+ caml-match-indent c)))
1739     (insert "match\n\nwith\n")
1740     (indent-line-to i)
1741     (push-mark)
1742     (forward-line -1)
1743     (indent-line-to c)
1744     (forward-line -1)
1745     (indent-line-to i)))
1746
1747 (defun caml-insert-let-form ()
1748   "Insert nicely formatted let-in form leaving mark after in."
1749   (interactive "*")
1750   (let ((prec (preceding-char)))
1751     (if (and (numberp prec) (not (char-equal ?\  (char-syntax prec))))
1752         (insert " ")))
1753   (let* ((c (current-indentation)))
1754     (insert "let  in\n")
1755     (indent-line-to c)
1756     (push-mark)
1757     (forward-line -1)
1758     (forward-char (+ c 4))))
1759
1760 (defun caml-insert-try-form ()
1761   "Insert nicely formatted try-with form leaving mark after with."
1762   (interactive "*")
1763   (let ((prec (preceding-char)))
1764     (if (and (numberp prec) (not (char-equal ?\  (char-syntax prec))))
1765         (insert " ")))
1766   (let* ((c (current-indentation)) (i (+ caml-try-indent c)))
1767     (insert "try\n\nwith\n")
1768     (indent-line-to i)
1769     (push-mark)
1770     (forward-line -1)
1771     (indent-line-to c)
1772     (forward-line -1)
1773     (indent-line-to i)))
1774
1775 (defun caml-insert-while-form ()
1776   "Insert nicely formatted while-do-done form leaving mark after do, done."
1777   (interactive "*")
1778   (let ((prec (preceding-char)))
1779     (if (and (numberp prec) (not (char-equal ?\  (char-syntax prec))))
1780         (insert " ")))
1781   (let* ((c (current-indentation)) (i (+ caml-if-indent c)))
1782     (insert "while  do\n\ndone")
1783     (push-mark)
1784     (indent-line-to c)
1785     (forward-line -1)
1786     (indent-line-to i)
1787     (push-mark)
1788     (beginning-of-line 1)
1789     (backward-char 4)))
1790
1791 (autoload 'run-caml "inf-caml" "Run an inferior Caml process." t)
1792
1793 ;;;###autoload(add-to-list 'auto-mode-alist '("\\.ml[iylp]?$" . caml-mode))
1794
1795 (if window-system (require 'caml-font))
1796
1797 (provide 'caml)
1798
1799 ;;; caml.el ends here