Initial Commit
[packages] / xemacs-packages / ruby-modes / ruby-mode.el
1 ;;;
2 ;;;  ruby-mode.el -
3 ;;;
4 ;;;  $Author: knu $
5 ;;;  $Date: 2008-05-19 00:02:36 +0900 (Mon, 19 May 2008) $
6 ;;;  created at: Fri Feb  4 14:49:13 JST 1994
7 ;;;
8
9 (defconst ruby-mode-revision "$Revision: 16458 $")
10
11 (defconst ruby-mode-version
12   (progn
13    (string-match "[0-9.]+" ruby-mode-revision)
14    (substring ruby-mode-revision (match-beginning 0) (match-end 0))))
15
16 (defgroup ruby nil
17   "Major mode for editing ruby scripts."
18   :group 'languages
19   :prefix "ruby-")
20
21 (defcustom ruby-indent-level 2
22   "*Indentation of ruby statements."
23   :type 'integer
24   :group 'ruby)
25
26 (defconst ruby-block-beg-re
27   "class\\|module\\|def\\|if\\|unless\\|case\\|while\\|until\\|for\\|begin\\|do"
28   )
29
30 (defconst ruby-non-block-do-re
31   "\\(while\\|until\\|for\\|rescue\\)\\>[^_]"
32   )
33
34 (defconst ruby-indent-beg-re
35   "\\(\\s *\\(class\\|module\\|def\\)\\)\\|if\\|unless\\|case\\|while\\|until\\|for\\|begin"
36     )
37
38 (defconst ruby-modifier-beg-re
39   "if\\|unless\\|while\\|until"
40   )
41
42 (defconst ruby-modifier-re
43   (concat ruby-modifier-beg-re "\\|rescue")
44   )
45
46 (defconst ruby-block-mid-re
47   "then\\|else\\|elsif\\|when\\|rescue\\|ensure"
48   )
49
50 (defconst ruby-block-op-re
51   "and\\|or\\|not"
52   )
53
54 (defconst ruby-block-hanging-re
55   (concat ruby-modifier-beg-re "\\|" ruby-block-op-re)
56   )
57
58 (defconst ruby-block-end-re "\\<end\\>")
59
60 (defconst ruby-here-doc-beg-re
61   "<<\\(-\\)?\\(\\([a-zA-Z0-9_]+\\)\\|[\"]\\([^\"]+\\)[\"]\\|[']\\([^']+\\)[']\\)")
62
63 (defun ruby-here-doc-end-match ()
64   (concat "^"
65           (if (match-string 1) "[ \t]*" nil)
66           (regexp-quote
67            (or (match-string 3)
68                (match-string 4)
69                (match-string 5)))))
70
71 (defconst ruby-delimiter
72   (concat "[?$/%(){}#\"'`.:]\\|<<\\|\\[\\|\\]\\|\\<\\("
73           ruby-block-beg-re
74           "\\)\\>\\|" ruby-block-end-re
75           "\\|^=begin\\|" ruby-here-doc-beg-re)
76   )
77
78 (defconst ruby-negative
79   (concat "^[ \t]*\\(\\(" ruby-block-mid-re "\\)\\>\\|"
80             ruby-block-end-re "\\|}\\|\\]\\)")
81   )
82
83 (defconst ruby-operator-chars "-,.+*/%&|^~=<>:")
84 (defconst ruby-operator-re (concat "[" ruby-operator-chars "]"))
85
86 (defconst ruby-symbol-chars "a-zA-Z0-9_")
87 (defconst ruby-symbol-re (concat "[" ruby-symbol-chars "]"))
88
89 (defvar ruby-mode-abbrev-table nil
90   "Abbrev table in use in `ruby-mode' buffers.")
91
92 (define-abbrev-table 'ruby-mode-abbrev-table ())
93
94 (defvar ruby-mode-map nil "Keymap used in `ruby-mode'.")
95
96 (if ruby-mode-map
97     nil
98   (setq ruby-mode-map (make-sparse-keymap))
99   (define-key ruby-mode-map "{" 'ruby-electric-brace)
100   (define-key ruby-mode-map "}" 'ruby-electric-brace)
101   (define-key ruby-mode-map "\e\C-a" 'ruby-beginning-of-defun)
102   (define-key ruby-mode-map "\e\C-e" 'ruby-end-of-defun)
103   (define-key ruby-mode-map "\e\C-b" 'ruby-backward-sexp)
104   (define-key ruby-mode-map "\e\C-f" 'ruby-forward-sexp)
105   (define-key ruby-mode-map "\e\C-p" 'ruby-beginning-of-block)
106   (define-key ruby-mode-map "\e\C-n" 'ruby-end-of-block)
107   (define-key ruby-mode-map "\e\C-h" 'ruby-mark-defun)
108   (define-key ruby-mode-map "\e\C-q" 'ruby-indent-exp)
109   (define-key ruby-mode-map "\t" 'ruby-indent-command)
110   (define-key ruby-mode-map "\C-c\C-e" 'ruby-insert-end)
111   (define-key ruby-mode-map "\C-j" 'ruby-reindent-then-newline-and-indent)
112   (define-key ruby-mode-map "\C-m" 'newline))
113
114 (defvar ruby-mode-syntax-table nil
115   "Syntax table in use in `ruby-mode' buffers.")
116
117 (if ruby-mode-syntax-table
118     ()
119   (setq ruby-mode-syntax-table (make-syntax-table))
120   (modify-syntax-entry ?\' "\"" ruby-mode-syntax-table)
121   (modify-syntax-entry ?\" "\"" ruby-mode-syntax-table)
122   (modify-syntax-entry ?\` "\"" ruby-mode-syntax-table)
123   (modify-syntax-entry ?# "<" ruby-mode-syntax-table)
124   (modify-syntax-entry ?\n ">" ruby-mode-syntax-table)
125   (modify-syntax-entry ?\\ "\\" ruby-mode-syntax-table)
126   (modify-syntax-entry ?$ "." ruby-mode-syntax-table)
127   (modify-syntax-entry ?? "_" ruby-mode-syntax-table)
128   (modify-syntax-entry ?_ "_" ruby-mode-syntax-table)
129   (modify-syntax-entry ?< "." ruby-mode-syntax-table)
130   (modify-syntax-entry ?> "." ruby-mode-syntax-table)
131   (modify-syntax-entry ?& "." ruby-mode-syntax-table)
132   (modify-syntax-entry ?| "." ruby-mode-syntax-table)
133   (modify-syntax-entry ?% "." ruby-mode-syntax-table)
134   (modify-syntax-entry ?= "." ruby-mode-syntax-table)
135   (modify-syntax-entry ?/ "." ruby-mode-syntax-table)
136   (modify-syntax-entry ?+ "." ruby-mode-syntax-table)
137   (modify-syntax-entry ?* "." ruby-mode-syntax-table)
138   (modify-syntax-entry ?- "." ruby-mode-syntax-table)
139   (modify-syntax-entry ?\; "." ruby-mode-syntax-table)
140   (modify-syntax-entry ?\( "()" ruby-mode-syntax-table)
141   (modify-syntax-entry ?\) ")(" ruby-mode-syntax-table)
142   (modify-syntax-entry ?\{ "(}" ruby-mode-syntax-table)
143   (modify-syntax-entry ?\} "){" ruby-mode-syntax-table)
144   (modify-syntax-entry ?\[ "(]" ruby-mode-syntax-table)
145   (modify-syntax-entry ?\] ")[" ruby-mode-syntax-table)
146   )
147
148 (defcustom ruby-indent-tabs-mode nil
149   "*Indentation can insert tabs in ruby mode if this is non-nil."
150   :type 'boolean :group 'ruby)
151
152 (defcustom ruby-indent-level 2
153   "*Indentation of ruby statements."
154   :type 'integer :group 'ruby)
155
156 (defcustom ruby-comment-column 32
157   "*Indentation column of comments."
158   :type 'integer :group 'ruby)
159
160 (defcustom ruby-deep-arglist t
161   "*Deep indent lists in parenthesis when non-nil.
162 Also ignores spaces after parenthesis when 'space."
163   :group 'ruby)
164
165 (defcustom ruby-deep-indent-paren '(?\( ?\[ ?\] t)
166   "*Deep indent lists in parenthesis when non-nil. t means continuous line.
167 Also ignores spaces after parenthesis when 'space."
168   :group 'ruby)
169
170 (defcustom ruby-deep-indent-paren-style 'space
171   "Default deep indent style."
172   :options '(t nil space) :group 'ruby)
173
174 (eval-when-compile (require 'cl))
175 (defun ruby-imenu-create-index-in-block (prefix beg end)
176   (let ((index-alist '()) (case-fold-search nil)
177         name next pos decl sing)
178     (goto-char beg)
179     (while (re-search-forward "^\\s *\\(\\(class\\>\\(\\s *<<\\)?\\|module\\>\\)\\s *\\([^\(<\n ]+\\)\\|\\(def\\|alias\\)\\>\\s *\\([^\(\n ]+\\)\\)" end t)
180       (setq sing (match-beginning 3))
181       (setq decl (match-string 5))
182       (setq next (match-end 0))
183       (setq name (or (match-string 4) (match-string 6)))
184       (setq pos (match-beginning 0))
185       (cond
186        ((string= "alias" decl)
187         (if prefix (setq name (concat prefix name)))
188         (push (cons name pos) index-alist))
189        ((string= "def" decl)
190         (if prefix
191             (setq name
192                   (cond
193                    ((string-match "^self\." name)
194                     (concat (substring prefix 0 -1) (substring name 4)))
195                   (t (concat prefix name)))))
196         (push (cons name pos) index-alist)
197         (ruby-accurate-end-of-block end))
198        (t
199         (if (string= "self" name)
200             (if prefix (setq name (substring prefix 0 -1)))
201           (if prefix (setq name (concat (substring prefix 0 -1) "::" name)))
202           (push (cons name pos) index-alist))
203         (ruby-accurate-end-of-block end)
204         (setq beg (point))
205         (setq index-alist
206               (nconc (ruby-imenu-create-index-in-block
207                       (concat name (if sing "." "#"))
208                       next beg) index-alist))
209         (goto-char beg))))
210     index-alist))
211
212 (defun ruby-imenu-create-index ()
213   (nreverse (ruby-imenu-create-index-in-block nil (point-min) nil)))
214
215 (defun ruby-accurate-end-of-block (&optional end)
216   (let (state)
217     (or end (setq end (point-max)))
218     (while (and (setq state (apply 'ruby-parse-partial end state))
219                 (>= (nth 2 state) 0) (< (point) end)))))
220
221 (defun ruby-mode-variables ()
222   (set-syntax-table ruby-mode-syntax-table)
223   (setq local-abbrev-table ruby-mode-abbrev-table)
224   (make-local-variable 'indent-line-function)
225   (setq indent-line-function 'ruby-indent-line)
226   (make-local-variable 'require-final-newline)
227   (setq require-final-newline t)
228   (make-variable-buffer-local 'comment-start)
229   (setq comment-start "# ")
230   (make-variable-buffer-local 'comment-end)
231   (setq comment-end "")
232   (make-variable-buffer-local 'comment-column)
233   (setq comment-column ruby-comment-column)
234   (make-variable-buffer-local 'comment-start-skip)
235   (setq comment-start-skip "#+ *")
236   (setq indent-tabs-mode ruby-indent-tabs-mode)
237   (make-local-variable 'parse-sexp-ignore-comments)
238   (setq parse-sexp-ignore-comments t)
239   (make-local-variable 'paragraph-start)
240   (setq paragraph-start (concat "$\\|" page-delimiter))
241   (make-local-variable 'paragraph-separate)
242   (setq paragraph-separate paragraph-start)
243   (make-local-variable 'paragraph-ignore-fill-prefix)
244   (setq paragraph-ignore-fill-prefix t))
245
246 ;;;###autoload
247 (defun ruby-mode ()
248   "Major mode for editing ruby scripts.
249 \\[ruby-indent-command] properly indents subexpressions of multi-line
250 class, module, def, if, while, for, do, and case statements, taking
251 nesting into account.
252
253 The variable `ruby-indent-level' controls the amount of indentation.
254 \\{ruby-mode-map}"
255   (interactive)
256   (kill-all-local-variables)
257   (use-local-map ruby-mode-map)
258   (setq mode-name "Ruby")
259   (setq major-mode 'ruby-mode)
260   (ruby-mode-variables)
261
262   (make-local-variable 'imenu-create-index-function)
263   (setq imenu-create-index-function 'ruby-imenu-create-index)
264
265   (make-local-variable 'add-log-current-defun-function)
266   (setq add-log-current-defun-function 'ruby-add-log-current-method)
267
268   (set (make-local-variable 'font-lock-defaults) '((ruby-font-lock-keywords) nil nil))
269   (set (make-local-variable 'font-lock-keywords) ruby-font-lock-keywords)
270   (set (make-local-variable 'font-lock-syntax-table) ruby-font-lock-syntax-table)
271   (set (make-local-variable 'font-lock-syntactic-keywords) ruby-font-lock-syntactic-keywords)
272
273   (run-mode-hooks 'ruby-mode-hook))
274
275 (defun ruby-current-indentation ()
276   (save-excursion
277     (beginning-of-line)
278     (back-to-indentation)
279     (current-column)))
280
281 (defun ruby-indent-line (&optional flag)
282   "Correct indentation of the current ruby line."
283   (ruby-indent-to (ruby-calculate-indent)))
284
285 (defun ruby-indent-command ()
286   (interactive)
287   (ruby-indent-line t))
288
289 (defun ruby-indent-to (x)
290   (if x
291       (let (shift top beg)
292         (and (< x 0) (error "invalid nest"))
293         (setq shift (current-column))
294         (beginning-of-line)
295         (setq beg (point))
296         (back-to-indentation)
297         (setq top (current-column))
298         (skip-chars-backward " \t")
299         (if (>= shift top) (setq shift (- shift top))
300           (setq shift 0))
301         (if (and (bolp)
302                  (= x top))
303             (move-to-column (+ x shift))
304           (move-to-column top)
305           (delete-region beg (point))
306           (beginning-of-line)
307           (indent-to x)
308           (move-to-column (+ x shift))))))
309
310 (defun ruby-special-char-p (&optional pnt)
311   (setq pnt (or pnt (point)))
312   (let ((c (char-before pnt)) (b (and (< (point-min) pnt) (char-before (1- pnt)))))
313     (cond ((or (eq c ??) (eq c ?$)))
314           ((and (eq c ?:) (or (not b) (eq (char-syntax b) ? ))))
315           ((eq c ?\\) (eq b ??)))))
316
317 (defun ruby-expr-beg (&optional option)
318   (save-excursion
319     (store-match-data nil)
320     (let ((space (skip-chars-backward " \t"))
321           (start (point)))
322       (cond
323        ((bolp) t)
324        ((progn
325           (forward-char -1)
326           (and (looking-at "\\?")
327                (or (eq (char-syntax (char-before (point))) ?w)
328                    (ruby-special-char-p))))
329         nil)
330        ((and (eq option 'heredoc) (< space 0)) t)
331        ((or (looking-at ruby-operator-re)
332             (looking-at "[\\[({,;]")
333             (and (looking-at "[!?]")
334                  (or (not (eq option 'modifier))
335                      (bolp)
336                      (save-excursion (forward-char -1) (looking-at "\\Sw$"))))
337             (and (looking-at ruby-symbol-re)
338                  (skip-chars-backward ruby-symbol-chars)
339                  (cond
340                   ((or (looking-at (concat "\\<\\(" ruby-block-beg-re
341                                            "|" ruby-block-op-re
342                                            "|" ruby-block-mid-re "\\)\\>")))
343                    (goto-char (match-end 0))
344                    (not (looking-at "\\s_")))
345                   ((eq option 'expr-qstr)
346                    (looking-at "[a-zA-Z][a-zA-z0-9_]* +%[^ \t]"))
347                   ((eq option 'expr-re)
348                    (looking-at "[a-zA-Z][a-zA-z0-9_]* +/[^ \t]"))
349                   (t nil)))))))))
350
351 (defun ruby-forward-string (term &optional end no-error expand)
352   (let ((n 1) (c (string-to-char term))
353         (re (if expand
354                 (concat "[^\\]\\(\\\\\\\\\\)*\\([" term "]\\|\\(#{\\)\\)")
355               (concat "[^\\]\\(\\\\\\\\\\)*[" term "]"))))
356     (while (and (re-search-forward re end no-error)
357                 (if (match-beginning 3)
358                     (ruby-forward-string "}{" end no-error nil)
359                   (> (setq n (if (eq (char-before (point)) c)
360                                      (1- n) (1+ n))) 0)))
361       (forward-char -1))
362     (cond ((zerop n))
363           (no-error nil)
364           ((error "unterminated string")))))
365
366 (defun ruby-deep-indent-paren-p (c)
367   (cond ((listp ruby-deep-indent-paren)
368          (let ((deep (assoc c ruby-deep-indent-paren)))
369            (cond (deep
370                   (or (cdr deep) ruby-deep-indent-paren-style))
371                  ((memq c ruby-deep-indent-paren)
372                   ruby-deep-indent-paren-style))))
373         ((eq c ruby-deep-indent-paren) ruby-deep-indent-paren-style)
374         ((eq c ?\( ) ruby-deep-arglist)))
375
376 (defun ruby-parse-partial (&optional end in-string nest depth pcol indent)
377   (or depth (setq depth 0))
378   (or indent (setq indent 0))
379   (when (re-search-forward ruby-delimiter end 'move)
380     (let ((pnt (point)) w re expand)
381       (goto-char (match-beginning 0))
382       (cond
383        ((and (memq (char-before) '(?@ ?$)) (looking-at "\\sw"))
384         (goto-char pnt))
385        ((looking-at "[\"`]")            ;skip string
386         (cond
387          ((and (not (eobp))
388                (ruby-forward-string (buffer-substring (point) (1+ (point))) end t t))
389           nil)
390          (t
391           (setq in-string (point))
392           (goto-char end))))
393        ((looking-at "'")
394         (cond
395          ((and (not (eobp))
396                (re-search-forward "[^\\]\\(\\\\\\\\\\)*'" end t))
397           nil)
398          (t
399           (setq in-string (point))
400           (goto-char end))))
401        ((looking-at "/=") 
402         (goto-char pnt))
403        ((looking-at "/")
404         (cond
405          ((and (not (eobp)) (ruby-expr-beg 'expr-re))
406           (if (ruby-forward-string "/" end t t)
407               nil
408             (setq in-string (point))
409             (goto-char end)))
410          (t
411           (goto-char pnt))))
412        ((looking-at "%")
413         (cond
414          ((and (not (eobp))
415                (ruby-expr-beg 'expr-qstr)
416                (not (looking-at "%="))
417                (looking-at "%[QqrxWw]?\\([^a-zA-Z0-9 \t\n]\\)"))
418           (goto-char (match-beginning 1))
419           (setq expand (not (memq (char-before) '(?q ?w))))
420           (setq w (match-string 1))
421           (cond
422            ((string= w "[") (setq re "]["))
423            ((string= w "{") (setq re "}{"))
424            ((string= w "(") (setq re ")("))
425            ((string= w "<") (setq re "><"))
426            ((and expand (string= w "\\"))
427             (setq w (concat "\\" w))))
428           (unless (cond (re (ruby-forward-string re end t expand))
429                         (expand (ruby-forward-string w end t t))
430                         (t (re-search-forward
431                             (if (string= w "\\")
432                                 "\\\\[^\\]*\\\\"
433                               (concat "[^\\]\\(\\\\\\\\\\)*" w))
434                             end t)))
435             (setq in-string (point))
436             (goto-char end)))
437          (t
438           (goto-char pnt))))
439        ((looking-at "\\?")              ;skip ?char
440         (cond
441          ((and (ruby-expr-beg)
442                (looking-at "?\\(\\\\C-\\|\\\\M-\\)*\\\\?."))
443           (goto-char (match-end 0)))
444          (t
445           (goto-char pnt))))
446        ((looking-at "\\$")              ;skip $char
447         (goto-char pnt)
448         (forward-char 1))
449        ((looking-at "#")                ;skip comment
450         (forward-line 1)
451         (goto-char (point))
452         )
453        ((looking-at "[\\[{(]")
454         (let ((deep (ruby-deep-indent-paren-p (char-after))))
455           (if (and deep (or (not (eq (char-after) ?\{)) (ruby-expr-beg)))
456               (progn
457                 (and (eq deep 'space) (looking-at ".\\s +[^# \t\n]")
458                      (setq pnt (1- (match-end 0))))
459                 (setq nest (cons (cons (char-after (point)) pnt) nest))
460                 (setq pcol (cons (cons pnt depth) pcol))
461                 (setq depth 0))
462             (setq nest (cons (cons (char-after (point)) pnt) nest))
463             (setq depth (1+ depth))))
464         (goto-char pnt)
465         )
466        ((looking-at "[])}]")
467         (if (ruby-deep-indent-paren-p (matching-paren (char-after)))
468             (setq depth (cdr (car pcol)) pcol (cdr pcol))
469           (setq depth (1- depth)))
470         (setq nest (cdr nest))
471         (goto-char pnt))
472        ((looking-at ruby-block-end-re)
473         (if (or (and (not (bolp))
474                      (progn
475                        (forward-char -1)
476                        (setq w (char-after (point)))
477                        (or (eq ?_ w)
478                            (eq ?. w))))
479                 (progn
480                   (goto-char pnt)
481                   (setq w (char-after (point)))
482                   (or (eq ?_ w)
483                       (eq ?! w)
484                       (eq ?? w))))
485             nil
486           (setq nest (cdr nest))
487           (setq depth (1- depth)))
488         (goto-char pnt))
489        ((looking-at "def\\s +[^(\n;]*")
490         (if (or (bolp)
491                 (progn
492                   (forward-char -1)
493                   (not (eq ?_ (char-after (point))))))
494             (progn
495               (setq nest (cons (cons nil pnt) nest))
496               (setq depth (1+ depth))))
497         (goto-char (match-end 0)))
498        ((looking-at (concat "\\<\\(" ruby-block-beg-re "\\)\\>"))
499         (and
500          (save-match-data
501            (or (not (looking-at "do\\>[^_]"))
502                (save-excursion
503                  (back-to-indentation)
504                  (not (looking-at ruby-non-block-do-re)))))
505          (or (bolp)
506              (progn
507                (forward-char -1)
508                (setq w (char-after (point)))
509                (not (or (eq ?_ w)
510                         (eq ?. w)))))
511          (goto-char pnt)
512          (setq w (char-after (point)))
513          (not (eq ?_ w))
514          (not (eq ?! w))
515          (not (eq ?? w))
516          (skip-chars-forward " \t")
517          (goto-char (match-beginning 0))
518          (or (not (looking-at ruby-modifier-re))
519              (ruby-expr-beg 'modifier))
520          (goto-char pnt)
521          (setq nest (cons (cons nil pnt) nest))
522          (setq depth (1+ depth)))
523         (goto-char pnt))
524        ((looking-at ":\\(['\"]\\)")
525         (goto-char (match-beginning 1))
526         (ruby-forward-string (buffer-substring (match-beginning 1) (match-end 1)) end))
527        ((looking-at ":\\([-,.+*/%&|^~<>]=?\\|===?\\|<=>\\)")
528         (goto-char (match-end 0)))
529        ((looking-at ":\\([a-zA-Z_][a-zA-Z_0-9]*[!?=]?\\)?")
530         (goto-char (match-end 0)))
531        ((or (looking-at "\\.\\.\\.?")
532             (looking-at "\\.[0-9]+")
533             (looking-at "\\.[a-zA-Z_0-9]+")
534             (looking-at "\\."))
535         (goto-char (match-end 0)))
536        ((looking-at "^=begin")
537         (if (re-search-forward "^=end" end t)
538             (forward-line 1)
539           (setq in-string (match-end 0))
540           (goto-char end)))
541        ((looking-at "<<")
542         (cond
543          ((and (ruby-expr-beg 'heredoc)
544                (looking-at "<<\\(-\\)?\\(\\([\"'`]\\)\\([^\n]+?\\)\\3\\|\\(?:\\sw\\|\\s_\\)+\\)"))
545           (setq re (regexp-quote (or (match-string 4) (match-string 2))))
546           (if (match-beginning 1) (setq re (concat "\\s *" re)))
547           (let* ((id-end (goto-char (match-end 0)))
548                  (line-end-position (save-excursion (end-of-line) (point)))
549                  (state (list in-string nest depth pcol indent)))
550             ;; parse the rest of the line
551             (while (and (> line-end-position (point))
552                         (setq state (apply 'ruby-parse-partial
553                                            line-end-position state))))
554             (setq in-string (car state)
555                   nest (nth 1 state)
556                   depth (nth 2 state)
557                   pcol (nth 3 state)
558                   indent (nth 4 state))
559             ;; skip heredoc section
560             (if (re-search-forward (concat "^" re "$") end 'move)
561                 (forward-line 1)
562               (setq in-string id-end)
563               (goto-char end))))
564          (t
565           (goto-char pnt))))
566        ((looking-at "^__END__$")
567         (goto-char pnt))
568        ((looking-at ruby-here-doc-beg-re)
569         (if (re-search-forward (ruby-here-doc-end-match)
570                                indent-point t)
571             (forward-line 1)
572           (setq in-string (match-end 0))
573           (goto-char indent-point)))
574        (t
575         (error (format "bad string %s"
576                        (buffer-substring (point) pnt)
577                        ))))))
578   (list in-string nest depth pcol))
579
580 (defun ruby-parse-region (start end)
581   (let (state)
582     (save-excursion
583       (if start
584           (goto-char start)
585         (ruby-beginning-of-indent))
586       (save-restriction
587         (narrow-to-region (point) end)
588         (while (and (> end (point))
589                     (setq state (apply 'ruby-parse-partial end state))))))
590     (list (nth 0 state)                 ; in-string
591           (car (nth 1 state))           ; nest
592           (nth 2 state)                 ; depth
593           (car (car (nth 3 state)))     ; pcol
594           ;(car (nth 5 state))          ; indent
595           )))
596
597 (defun ruby-indent-size (pos nest)
598   (+ pos (* (or nest 1) ruby-indent-level)))
599
600 (defun ruby-calculate-indent (&optional parse-start)
601   (save-excursion
602     (beginning-of-line)
603     (let ((indent-point (point))
604           (case-fold-search nil)
605           state bol eol begin op-end
606           (paren (progn (skip-syntax-forward " ")
607                         (and (char-after) (matching-paren (char-after)))))
608           (indent 0))
609       (if parse-start
610           (goto-char parse-start)
611         (ruby-beginning-of-indent)
612         (setq parse-start (point)))
613       (back-to-indentation)
614       (setq indent (current-column))
615       (setq state (ruby-parse-region parse-start indent-point))
616       (cond
617        ((nth 0 state)                   ; within string
618         (setq indent nil))              ;  do nothing
619        ((car (nth 1 state))             ; in paren
620         (goto-char (setq begin (cdr (nth 1 state))))
621         (let ((deep (ruby-deep-indent-paren-p (car (nth 1 state)))))
622           (if deep
623               (cond ((and (eq deep t) (eq (car (nth 1 state)) paren))
624                      (skip-syntax-backward " ")
625                      (setq indent (1- (current-column))))
626                     ((let ((s (ruby-parse-region (point) indent-point)))
627                        (and (nth 2 s) (> (nth 2 s) 0)
628                             (or (goto-char (cdr (nth 1 s))) t)))
629                      (forward-word -1)
630                      (setq indent (ruby-indent-size (current-column) (nth 2 state))))
631                     (t
632                      (setq indent (current-column))
633                      (cond ((eq deep 'space))
634                            (paren (setq indent (1- indent)))
635                            (t (setq indent (ruby-indent-size (1- indent) 1))))))
636             (if (nth 3 state) (goto-char (nth 3 state))
637               (goto-char parse-start) (back-to-indentation))
638             (setq indent (ruby-indent-size (current-column) (nth 2 state))))
639           (and (eq (car (nth 1 state)) paren)
640                (ruby-deep-indent-paren-p (matching-paren paren))
641                (search-backward (char-to-string paren))
642                (setq indent (current-column)))))
643        ((and (nth 2 state) (> (nth 2 state) 0)) ; in nest
644         (if (null (cdr (nth 1 state)))
645             (error "invalid nest"))
646         (goto-char (cdr (nth 1 state)))
647         (forward-word -1)               ; skip back a keyword
648         (setq begin (point))
649         (cond
650          ((looking-at "do\\>[^_]")      ; iter block is a special case
651           (if (nth 3 state) (goto-char (nth 3 state))
652             (goto-char parse-start) (back-to-indentation))
653           (setq indent (ruby-indent-size (current-column) (nth 2 state))))
654          (t
655           (setq indent (+ (current-column) ruby-indent-level)))))
656        
657        ((and (nth 2 state) (< (nth 2 state) 0)) ; in negative nest
658         (setq indent (ruby-indent-size (current-column) (nth 2 state)))))
659       (when indent
660         (goto-char indent-point)
661         (end-of-line)
662         (setq eol (point))
663         (beginning-of-line)
664         (cond
665          ((and (not (ruby-deep-indent-paren-p paren))
666                (re-search-forward ruby-negative eol t))
667           (and (not (eq ?_ (char-after (match-end 0))))
668                (setq indent (- indent ruby-indent-level))))
669          ((and
670            (save-excursion
671              (beginning-of-line)
672              (not (bobp)))
673            (or (ruby-deep-indent-paren-p t)
674                (null (car (nth 1 state)))))
675           ;; goto beginning of non-empty no-comment line
676           (let (end done)
677             (while (not done)
678               (skip-chars-backward " \t\n")
679               (setq end (point))
680               (beginning-of-line)
681               (if (re-search-forward "^\\s *#" end t)
682                   (beginning-of-line)
683                 (setq done t))))
684           (setq bol (point))
685           (end-of-line)
686           ;; skip the comment at the end
687           (skip-chars-backward " \t")
688           (let (end (pos (point)))
689             (beginning-of-line)
690             (while (and (re-search-forward "#" pos t)
691                         (setq end (1- (point)))
692                         (or (ruby-special-char-p end)
693                             (and (setq state (ruby-parse-region parse-start end))
694                                  (nth 0 state))))
695               (setq end nil))
696             (goto-char (or end pos))
697             (skip-chars-backward " \t")
698             (setq begin (if (nth 0 state) pos (cdr (nth 1 state))))
699             (setq state (ruby-parse-region parse-start (point))))
700           (or (bobp) (forward-char -1))
701           (and
702            (or (and (looking-at ruby-symbol-re)
703                     (skip-chars-backward ruby-symbol-chars)
704                     (looking-at (concat "\\<\\(" ruby-block-hanging-re "\\)\\>"))
705                     (not (eq (point) (nth 3 state)))
706                     (save-excursion
707                       (goto-char (match-end 0))
708                       (not (looking-at "[a-z_]"))))
709                (and (looking-at ruby-operator-re)
710                     (not (ruby-special-char-p))
711                     ;; operator at the end of line
712                     (let ((c (char-after (point))))
713                       (and
714 ;;                     (or (null begin)
715 ;;                         (save-excursion
716 ;;                           (goto-char begin)
717 ;;                           (skip-chars-forward " \t")
718 ;;                           (not (or (eolp) (looking-at "#")
719 ;;                                    (and (eq (car (nth 1 state)) ?{)
720 ;;                                         (looking-at "|"))))))
721                        (or (not (eq ?/ c))
722                            (null (nth 0 (ruby-parse-region (or begin parse-start) (point)))))
723                        (or (not (eq ?| (char-after (point))))
724                            (save-excursion
725                              (or (eolp) (forward-char -1))
726                              (cond
727                               ((search-backward "|" nil t)
728                                (skip-chars-backward " \t\n")
729                                (and (not (eolp))
730                                     (progn
731                                       (forward-char -1)
732                                       (not (looking-at "{")))
733                                     (progn
734                                       (forward-word -1)
735                                       (not (looking-at "do\\>[^_]")))))
736                               (t t))))
737                        (not (eq ?, c))
738                        (setq op-end t)))))
739            (setq indent
740                  (cond
741                   ((and
742                     (null op-end)
743                     (not (looking-at (concat "\\<\\(" ruby-block-hanging-re "\\)\\>")))
744                     (eq (ruby-deep-indent-paren-p t) 'space)
745                     (not (bobp)))
746                    (save-excursion
747                      (widen)
748                      (goto-char (or begin parse-start))
749                      (skip-syntax-forward " ")
750                      (current-column)))
751                   ((car (nth 1 state)) indent)
752                   (t
753                    (+ indent ruby-indent-level))))))))
754       indent)))
755
756 (defun ruby-electric-brace (arg)
757   (interactive "P")
758   (insert-char last-command-char 1)
759   (ruby-indent-line t)
760   (delete-char -1)
761   (self-insert-command (prefix-numeric-value arg)))
762
763 (eval-when-compile
764   (defmacro defun-region-command (func args &rest body)
765     (let ((intr (car body)))
766       (when (featurep 'xemacs)
767         (if (stringp intr) (setq intr (cadr body)))
768         (and (eq (car intr) 'interactive)
769              (setq intr (cdr intr))
770              (setcar intr (concat "_" (car intr)))))
771       (cons 'defun (cons func (cons args body))))))
772
773 (defun-region-command ruby-beginning-of-defun (&optional arg)
774   "Move backward to next beginning-of-defun.
775 With argument, do this that many times.
776 Returns t unless search stops due to end of buffer."
777   (interactive "p")
778   (and (re-search-backward (concat "^\\(" ruby-block-beg-re "\\)\\b")
779                            nil 'move (or arg 1))
780        (progn (beginning-of-line) t)))
781
782 (defun ruby-beginning-of-indent ()
783   (and (re-search-backward (concat "^\\(" ruby-indent-beg-re "\\)\\b")
784                            nil 'move)
785        (progn
786          (beginning-of-line)
787          t)))
788
789 (defun-region-command ruby-end-of-defun (&optional arg)
790   "Move forward to next end of defun.
791 An end of a defun is found by moving forward from the beginning of one."
792   (interactive "p")
793   (and (re-search-forward (concat "^\\(" ruby-block-end-re "\\)\\($\\|\\b[^_]\\)")
794                           nil 'move (or arg 1))
795        (progn (beginning-of-line) t))
796   (forward-line 1))
797
798 (defun ruby-move-to-block (n)
799   (let (start pos done down)
800     (setq start (ruby-calculate-indent))
801     (setq down (looking-at (if (< n 0) ruby-block-end-re
802                              (concat "\\<\\(" ruby-block-beg-re "\\)\\>"))))
803     (while (and (not done) (not (if (< n 0) (bobp) (eobp))))
804       (forward-line n)
805       (cond
806        ((looking-at "^\\s *$"))
807        ((looking-at "^\\s *#"))
808        ((and (> n 0) (looking-at "^=begin\\>"))
809         (re-search-forward "^=end\\>"))
810        ((and (< n 0) (looking-at "^=end\\>"))
811         (re-search-backward "^=begin\\>"))
812        (t
813         (setq pos (current-indentation))
814         (cond
815          ((< start pos)
816           (setq down t))
817          ((and down (= pos start))
818           (setq done t))
819          ((> start pos)
820           (setq done t)))))
821       (if done
822           (save-excursion
823             (back-to-indentation)
824             (if (looking-at (concat "\\<\\(" ruby-block-mid-re "\\)\\>"))
825                 (setq done nil))))))
826   (back-to-indentation))
827
828 (defun-region-command ruby-beginning-of-block (&optional arg)
829   "Move backward to next beginning-of-block"
830   (interactive "p")
831   (ruby-move-to-block (- (or arg 1))))
832
833 (defun-region-command ruby-end-of-block (&optional arg)
834   "Move forward to next beginning-of-block"
835   (interactive "p")
836   (ruby-move-to-block (or arg 1)))
837
838 (defun-region-command ruby-forward-sexp (&optional cnt)
839   (interactive "p")
840   (if (and (numberp cnt) (< cnt 0))
841       (ruby-backward-sexp (- cnt))
842     (let ((i (or cnt 1)))
843       (condition-case nil
844           (while (> i 0)
845             (skip-syntax-forward " ")
846             (cond ((looking-at "\\?\\(\\\\[CM]-\\)*\\\\?\\S ")
847                    (goto-char (match-end 0)))
848                   ((progn
849                      (skip-chars-forward ",.:;|&^~=!?\\+\\-\\*")
850                      (looking-at "\\s("))
851                    (goto-char (scan-sexps (point) 1)))
852                   ((and (looking-at (concat "\\<\\(" ruby-block-beg-re "\\)\\>"))
853                         (not (eq (char-before (point)) ?.))
854                         (not (eq (char-before (point)) ?:)))
855                    (ruby-end-of-block)
856                    (forward-word 1))
857                   ((looking-at "\\(\\$\\|@@?\\)?\\sw")
858                    (while (progn
859                             (while (progn (forward-word 1) (looking-at "_")))
860                             (cond ((looking-at "::") (forward-char 2) t)
861                                   ((> (skip-chars-forward ".") 0))
862                                   ((looking-at "\\?\\|!\\(=[~=>]\\|[^~=]\\)")
863                                    (forward-char 1) nil)))))
864                   ((let (state expr)
865                      (while
866                          (progn
867                            (setq expr (or expr (ruby-expr-beg)
868                                           (looking-at "%\\sw?\\Sw\\|[\"'`/]")))
869                            (nth 1 (setq state (apply 'ruby-parse-partial nil state))))
870                        (setq expr t)
871                        (skip-chars-forward "<"))
872                      (not expr))))
873             (setq i (1- i)))
874         ((error) (forward-word 1)))
875       i)))
876
877 (defun-region-command ruby-backward-sexp (&optional cnt)
878   (interactive "p")
879   (if (and (numberp cnt) (< cnt 0))
880       (ruby-forward-sexp (- cnt))
881     (let ((i (or cnt 1)))
882       (condition-case nil
883           (while (> i 0)
884             (skip-chars-backward " \t\n,.:;|&^~=!?\\+\\-\\*")
885             (forward-char -1)
886             (cond ((looking-at "\\s)")
887                    (goto-char (scan-sexps (1+ (point)) -1))
888                    (case (char-before)
889                      (?% (forward-char -1))
890                      ('(?q ?Q ?w ?W ?r ?x)
891                       (if (eq (char-before (1- (point))) ?%) (forward-char -2))))
892                    nil)
893                   ((looking-at "\\s\"\\|\\\\\\S_")
894                    (let ((c (char-to-string (char-before (match-end 0)))))
895                      (while (and (search-backward c)
896                                  (oddp (skip-chars-backward "\\")))))
897                    nil)
898                   ((looking-at "\\s.\\|\\s\\")
899                    (if (ruby-special-char-p) (forward-char -1)))
900                   ((looking-at "\\s(") nil)
901                   (t
902                    (forward-char 1)
903                    (while (progn (forward-word -1)
904                                  (case (char-before)
905                                    (?_ t)
906                                    (?. (forward-char -1) t)
907                                    ((?$ ?@)
908                                     (forward-char -1)
909                                     (and (eq (char-before) (char-after)) (forward-char -1)))
910                                    (?:
911                                     (forward-char -1)
912                                     (eq (char-before) :)))))
913                    (if (looking-at ruby-block-end-re)
914                        (ruby-beginning-of-block))
915                    nil))
916             (setq i (1- i)))
917         ((error)))
918       i)))
919
920 (defun ruby-reindent-then-newline-and-indent ()
921   (interactive "*")
922   (newline)
923   (save-excursion
924     (end-of-line 0)
925     (indent-according-to-mode)
926     (delete-region (point) (progn (skip-chars-backward " \t") (point))))
927   (indent-according-to-mode))
928
929 (fset 'ruby-encomment-region (symbol-function 'comment-region))
930
931 (defun ruby-decomment-region (beg end)
932   (interactive "r")
933   (save-excursion
934     (goto-char beg)
935     (while (re-search-forward "^\\([ \t]*\\)#" end t)
936       (replace-match "\\1" nil nil)
937       (save-excursion
938         (ruby-indent-line)))))
939
940 (defun ruby-insert-end ()
941   (interactive)
942   (insert "end")
943   (ruby-indent-line t)
944   (end-of-line))
945
946 (defun ruby-mark-defun ()
947   "Put mark at end of this Ruby function, point at beginning."
948   (interactive)
949   (push-mark (point))
950   (ruby-end-of-defun)
951   (push-mark (point) nil t)
952   (ruby-beginning-of-defun)
953   (re-search-backward "^\n" (- (point) 1) t))
954
955 (defun ruby-indent-exp (&optional shutup-p)
956   "Indent each line in the balanced expression following point syntactically.
957 If optional SHUTUP-P is non-nil, no errors are signalled if no
958 balanced expression is found."
959   (interactive "*P")
960   (let ((here (point-marker)) start top column (nest t))
961     (set-marker-insertion-type here t)
962     (unwind-protect
963         (progn
964           (beginning-of-line)
965           (setq start (point) top (current-indentation))
966           (while (and (not (eobp))
967                       (progn
968                         (setq column (ruby-calculate-indent start))
969                         (cond ((> column top)
970                                (setq nest t))
971                               ((and (= column top) nest)
972                                (setq nest nil) t))))
973             (ruby-indent-to column)
974             (beginning-of-line 2)))
975       (goto-char here)
976       (set-marker here nil))))
977
978 (defun ruby-add-log-current-method ()
979   "Return current method string."
980   (condition-case nil
981       (save-excursion
982         (let ((mlist nil) (indent 0))
983           ;; get current method (or class/module)
984           (if (re-search-backward
985                (concat "^[ \t]*\\(def\\|class\\|module\\)[ \t]+"
986                        "\\(" 
987                        ;; \\. for class method
988                         "\\(" ruby-symbol-re "\\|\\." "\\)" 
989                         "+\\)")
990                nil t)
991               (progn
992                 (setq mlist (list (match-string 2)))
993                 (goto-char (match-beginning 1))
994                 (setq indent (current-column))
995                 (beginning-of-line)))
996           ;; nest class/module
997           (while (and (> indent 0)
998                       (re-search-backward
999                        (concat
1000                         "^[ \t]*\\(class\\|module\\)[ \t]+"
1001                         "\\([A-Z]" ruby-symbol-re "+\\)")
1002                        nil t))
1003             (goto-char (match-beginning 1))
1004             (if (< (current-column) indent)
1005                 (progn
1006                   (setq mlist (cons (match-string 2) mlist))
1007                   (setq indent (current-column))
1008                   (beginning-of-line))))
1009           ;; generate string
1010           (if (consp mlist)
1011               (mapconcat (function identity) mlist "::")
1012             nil)))))
1013
1014 (cond
1015  ((featurep 'font-lock)
1016   (or (boundp 'font-lock-variable-name-face)
1017       (setq font-lock-variable-name-face font-lock-type-face))
1018
1019   (setq ruby-font-lock-syntactic-keywords
1020         '(
1021           ;; #{ }, #$hoge, #@foo are not comments
1022           ("\\(#\\)[{$@]" 1 (1 . nil))
1023           ;; the last $', $", $` in the respective string is not variable
1024           ;; the last ?', ?", ?` in the respective string is not ascii code
1025           ("\\(^\\|[\[ \t\n<+\(,=]\\)\\(['\"`]\\)\\(\\\\.\\|\\2\\|[^'\"`\n\\\\]\\)*?\\\\?[?$]\\(\\2\\)"
1026            (2 (7 . nil))
1027            (4 (7 . nil)))
1028           ;; $' $" $` .... are variables
1029           ;; ?' ?" ?` are ascii codes
1030           ("\\(^\\|[^\\\\]\\)\\(\\\\\\\\\\)*[?$]\\([#\"'`]\\)" 3 (1 . nil))
1031           ;; regexps
1032           ("\\(^\\|[=(,~?:;<>]\\|\\(^\\|\\s \\)\\(if\\|elsif\\|unless\\|while\\|until\\|when\\|and\\|or\\|&&\\|||\\)\\|g?sub!?\\|scan\\|split!?\\)\\s *\\(/\\)[^/\n\\\\]*\\(\\\\.[^/\n\\\\]*\\)*\\(/\\)"
1033            (4 (7 . ?/))
1034            (6 (7 . ?/)))
1035           ("^\\(=\\)begin\\(\\s \\|$\\)" 1 (7 . nil))
1036           ("^\\(=\\)end\\(\\s \\|$\\)" 1 (7 . nil))))
1037
1038   (if (featurep 'xemacs)
1039       (put 'ruby-mode 'font-lock-defaults
1040            '((ruby-font-lock-keywords)
1041              nil nil nil
1042              beginning-of-line
1043              (font-lock-syntactic-keywords
1044               . ruby-font-lock-syntactic-keywords))))
1045
1046   (defun ruby-font-lock-docs (limit)
1047     (if (re-search-forward "^=begin\\(\\s \\|$\\)" limit t)
1048         (let (beg)
1049           (beginning-of-line)
1050           (setq beg (point))
1051           (forward-line 1)
1052           (if (re-search-forward "^=end\\(\\s \\|$\\)" limit t)
1053               (progn
1054                 (set-match-data (list beg (point)))
1055                 t)))))
1056
1057   (defun ruby-font-lock-maybe-docs (limit)
1058     (let (beg)
1059       (save-excursion
1060         (if (and (re-search-backward "^=\\(begin\\|end\\)\\(\\s \\|$\\)" nil t)
1061                  (string= (match-string 1) "begin"))
1062             (progn
1063               (beginning-of-line)
1064               (setq beg (point)))))
1065       (if (and beg (and (re-search-forward "^=\\(begin\\|end\\)\\(\\s \\|$\\)" nil t)
1066                         (string= (match-string 1) "end")))
1067           (progn
1068             (set-match-data (list beg (point)))
1069             t)
1070         nil)))
1071
1072   (defvar ruby-font-lock-syntax-table
1073     (let* ((tbl (copy-syntax-table ruby-mode-syntax-table)))
1074       (modify-syntax-entry ?_ "w" tbl)
1075       tbl))
1076
1077   (defun ruby-font-lock-here-docs (limit)
1078     (if (re-search-forward ruby-here-doc-beg-re limit t)
1079         (let (beg)
1080           (beginning-of-line)
1081           (forward-line)
1082           (setq beg (point))
1083           (if (re-search-forward (ruby-here-doc-end-match) nil t)
1084               (progn
1085                 (set-match-data (list beg (point)))
1086                 t)))))
1087
1088   (defun ruby-font-lock-maybe-here-docs (limit)
1089     (let (beg)
1090       (save-excursion
1091         (if (re-search-backward ruby-here-doc-beg-re nil t)
1092             (progn
1093               (beginning-of-line)
1094               (forward-line)
1095               (setq beg (point)))))
1096       (if (and beg
1097                (let ((end-match (ruby-here-doc-end-match)))
1098                  (and (not (re-search-backward end-match beg t))
1099                       (re-search-forward end-match nil t))))
1100           (progn
1101             (set-match-data (list beg (point)))
1102             t)
1103           nil)))
1104
1105   (defvar ruby-font-lock-keywords
1106     (list
1107      ;; functions
1108      '("^\\s *def\\s +\\([^( \t\n]+\\)"
1109        1 font-lock-function-name-face)
1110      ;; keywords
1111      (cons (concat
1112             "\\(^\\|[^_:.@$]\\|\\.\\.\\)\\b\\(defined\\?\\|\\("
1113             (mapconcat
1114              'identity
1115              '("alias"
1116                "and"
1117                "begin"
1118                "break"
1119                "case"
1120                "catch"
1121                "class"
1122                "def"
1123                "do"
1124                "elsif"
1125                "else"
1126                "fail"
1127                "ensure"
1128                "for"
1129                "end"
1130                "if"
1131                "in"
1132                "module"
1133                "next"
1134                "not"
1135                "or"
1136                "raise"
1137                "redo"
1138                "rescue"
1139                "retry"
1140                "return"
1141                "then"
1142                "throw"
1143                "super"
1144                "unless"
1145                "undef"
1146                "until"
1147                "when"
1148                "while"
1149                "yield"
1150                )
1151              "\\|")
1152             "\\)\\>\\)")
1153            2)
1154      ;; variables
1155      '("\\(^\\|[^_:.@$]\\|\\.\\.\\)\\b\\(nil\\|self\\|true\\|false\\)\\>"
1156        2 font-lock-variable-name-face)
1157      ;; variables
1158      '("\\(\\$\\([^a-zA-Z0-9 \n]\\|[0-9]\\)\\)\\W"
1159        1 font-lock-variable-name-face)
1160      '("\\(\\$\\|@\\|@@\\)\\(\\w\\|_\\)+"
1161        0 font-lock-variable-name-face)
1162      ;; embedded document
1163      '(ruby-font-lock-docs
1164        0 font-lock-comment-face t)
1165      '(ruby-font-lock-maybe-docs
1166        0 font-lock-comment-face t)
1167      ;; "here" document
1168      '(ruby-font-lock-here-docs
1169        0 font-lock-string-face t)
1170      '(ruby-font-lock-maybe-here-docs
1171        0 font-lock-string-face t)
1172      `(,ruby-here-doc-beg-re
1173        0 font-lock-string-face t)
1174      ;; general delimited string
1175      '("\\(^\\|[[ \t\n<+(,=]\\)\\(%[xrqQwW]?\\([^<[{(a-zA-Z0-9 \n]\\)[^\n\\\\]*\\(\\\\.[^\n\\\\]*\\)*\\(\\3\\)\\)"
1176        (2 font-lock-string-face))
1177      ;; constants
1178      '("\\(^\\|[^_]\\)\\b\\([A-Z]+\\(\\w\\|_\\)*\\)"
1179        2 font-lock-type-face)
1180      ;; symbols
1181      '("\\(^\\|[^:]\\)\\(:\\([-+~]@?\\|[/%&|^`]\\|\\*\\*?\\|<\\(<\\|=>?\\)?\\|>[>=]?\\|===?\\|=~\\|\\[\\]=?\\|\\(\\w\\|_\\)+\\([!?=]\\|\\b_*\\)\\|#{[^}\n\\\\]*\\(\\\\.[^}\n\\\\]*\\)*}\\)\\)"
1182        2 font-lock-reference-face)
1183      ;; expression expansion
1184      '("#\\({[^}\n\\\\]*\\(\\\\.[^}\n\\\\]*\\)*}\\|\\(\\$\\|@\\|@@\\)\\(\\w\\|_\\)+\\)"
1185        0 font-lock-variable-name-face t)
1186      ;; warn lower camel case
1187      ;'("\\<[a-z]+[a-z0-9]*[A-Z][A-Za-z0-9]*\\([!?]?\\|\\>\\)"
1188      ;  0 font-lock-warning-face)
1189      )
1190     "*Additional expressions to highlight in ruby mode."))
1191
1192  ((featurep 'hilit19)
1193   (hilit-set-mode-patterns
1194    'ruby-mode
1195    '(("[^$\\?]\\(\"[^\\\"]*\\(\\\\\\(.\\|\n\\)[^\\\"]*\\)*\"\\)" 1 string)
1196      ("[^$\\?]\\('[^\\']*\\(\\\\\\(.\\|\n\\)[^\\']*\\)*'\\)" 1 string)
1197      ("[^$\\?]\\(`[^\\`]*\\(\\\\\\(.\\|\n\\)[^\\`]*\\)*`\\)" 1 string)
1198      ("^\\s *#.*$" nil comment)
1199      ("[^$@?\\]\\(#[^$@{\n].*$\\)" 1 comment)
1200      ("[^a-zA-Z_]\\(\\?\\(\\\\[CM]-\\)*.\\)" 1 string)
1201      ("^\\s *\\(require\\|load\\).*$" nil include)
1202      ("^\\s *\\(include\\|alias\\|undef\\).*$" nil decl)
1203      ("^\\s *\\<\\(class\\|def\\|module\\)\\>" "[)\n;]" defun)
1204      ("[^_]\\<\\(begin\\|case\\|else\\|elsif\\|end\\|ensure\\|for\\|if\\|unless\\|rescue\\|then\\|when\\|while\\|until\\|do\\|yield\\)\\>\\([^_]\\|$\\)" 1 defun)
1205      ("[^_]\\<\\(and\\|break\\|next\\|raise\\|fail\\|in\\|not\\|or\\|redo\\|retry\\|return\\|super\\|yield\\|catch\\|throw\\|self\\|nil\\)\\>\\([^_]\\|$\\)" 1 keyword)
1206      ("\\$\\(.\\|\\sw+\\)" nil type)
1207      ("[$@].[a-zA-Z_0-9]*" nil struct)
1208      ("^__END__" nil label))))
1209  )
1210
1211 ;; XEmacs addition
1212 ;;;###autoload(add-to-list 'auto-mode-alist '("\\.rb$" . ruby-mode))
1213 ;;;###autoload(add-to-list 'auto-mode-alist '("\\.rake$" . ruby-mode))
1214
1215 (provide 'ruby-mode)
1216
1217 ;;; ruby-mode.el ends here