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