mirror of
https://git.savannah.gnu.org/git/emacs.git
synced 2025-02-01 20:06:00 +00:00
Initial revision
This commit is contained in:
parent
7229064dbf
commit
745bc783eb
129
lisp/compare-w.el
Normal file
129
lisp/compare-w.el
Normal file
@ -0,0 +1,129 @@
|
||||
;; Compare text between windows for Emacs.
|
||||
;; Copyright (C) 1986, 1989 Free Software Foundation, Inc.
|
||||
|
||||
;; This file is part of GNU Emacs.
|
||||
|
||||
;; GNU Emacs is free software; you can redistribute it and/or modify
|
||||
;; it under the terms of the GNU General Public License as published by
|
||||
;; the Free Software Foundation; either version 1, or (at your option)
|
||||
;; any later version.
|
||||
|
||||
;; GNU Emacs is distributed in the hope that it will be useful,
|
||||
;; but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
;; GNU General Public License for more details.
|
||||
|
||||
;; You should have received a copy of the GNU General Public License
|
||||
;; along with GNU Emacs; see the file COPYING. If not, write to
|
||||
;; the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.
|
||||
|
||||
(provide 'compare-w)
|
||||
|
||||
(defvar compare-windows-whitespace " \t\n"
|
||||
"*String of characters considered whitespace for \\[compare-windows].
|
||||
Changes in whitespace are optionally ignored.
|
||||
|
||||
The value of `compare-windows-whitespace' may instead be a function; this
|
||||
function is called in each buffer, with point at the current scanning point.
|
||||
The function's job is to categorize any whitespace around (including before)
|
||||
point; it should also advance past any whitespace.
|
||||
|
||||
The function is passed one argument, the point where `compare-windows'
|
||||
was originally called; it should not consider any text before that point.
|
||||
If the function returns the same value for both buffers, then the
|
||||
whitespace is considered to match, and is skipped.")
|
||||
|
||||
(defvar compare-ignore-case nil
|
||||
"*Non-nil means \\[compare-windows] ignores case differences.")
|
||||
|
||||
;;;###autoload
|
||||
(defun compare-windows (ignore-whitespace)
|
||||
"Compare text in current window with text in next window.
|
||||
Compares the text starting at point in each window,
|
||||
moving over text in each one as far as they match.
|
||||
|
||||
A prefix arg means ignore changes in whitespace.
|
||||
The variable `compare-windows-whitespace' controls how whitespace is skipped.
|
||||
If `compare-ignore-case' is non-nil, changes in case are also ignored."
|
||||
(interactive "P")
|
||||
(let* (p1 p2 maxp1 maxp2 b1 b2 w2
|
||||
success size
|
||||
(opoint1 (point))
|
||||
opoint2
|
||||
(skip-whitespace (if ignore-whitespace
|
||||
compare-windows-whitespace))
|
||||
(skip-whitespace-regexp (concat "[" skip-whitespace "]+")))
|
||||
(setq p1 (point) b1 (current-buffer))
|
||||
(setq w2 (next-window (selected-window)))
|
||||
(if (eq w2 (selected-window))
|
||||
(error "No other window"))
|
||||
(setq p2 (window-point w2)
|
||||
b2 (window-buffer w2))
|
||||
(setq opoint2 p2)
|
||||
(setq maxp1 (point-max))
|
||||
(save-excursion
|
||||
(set-buffer b2)
|
||||
(setq maxp2 (point-max)))
|
||||
|
||||
(setq success t)
|
||||
(while success
|
||||
(setq success nil)
|
||||
;; if interrupted, show how far we've gotten
|
||||
(goto-char p1)
|
||||
(set-window-point w2 p2)
|
||||
|
||||
;; If both buffers have whitespace next to point,
|
||||
;; optionally skip over it.
|
||||
|
||||
(and skip-whitespace
|
||||
(save-excursion
|
||||
(let (p1a p2a w1 w2 result1 result2)
|
||||
(if (stringp skip-whitespace)
|
||||
(progn
|
||||
(if (not (eobp))
|
||||
(skip-chars-backward skip-whitespace opoint1))
|
||||
(and (looking-at skip-whitespace-regexp)
|
||||
(setq p1a (match-end 0) result1 t)))
|
||||
(setq result1 (funcall skip-whitespace opoint1))
|
||||
(setq p1a (point)))
|
||||
(set-buffer b2)
|
||||
(goto-char p2)
|
||||
(if (stringp skip-whitespace)
|
||||
(progn
|
||||
(if (not (eobp))
|
||||
(skip-chars-backward skip-whitespace opoint2))
|
||||
(and (looking-at skip-whitespace-regexp)
|
||||
(setq p2a (match-end 0) result2 t)))
|
||||
(setq result2 (funcall skip-whitespace opoint2))
|
||||
(setq p2a (point)))
|
||||
(and result1 result2 (eq result1 result2)
|
||||
(setq p1 p1a
|
||||
p2 p2a)))))
|
||||
|
||||
;; Try advancing comparing 1000 chars at a time.
|
||||
;; When that fails, go 500 chars at a time, and so on.
|
||||
(let ((size 1000)
|
||||
success-1)
|
||||
(while (> size 0)
|
||||
(setq success-1 t)
|
||||
(while success-1
|
||||
(setq size (min size (- maxp1 p1) (- maxp2 p2)))
|
||||
(save-excursion
|
||||
(set-buffer b2)
|
||||
(setq s2 (buffer-substring p2 (+ size p2))))
|
||||
(setq success-1
|
||||
(and (> size 0)
|
||||
(if compare-ignore-case
|
||||
(let ((case-fold-search t))
|
||||
(save-excursion
|
||||
(search-forward s2 (+ p1 size) t)))
|
||||
(equal (buffer-substring p1 (+ size p1)) s2))))
|
||||
(if success-1
|
||||
(setq p1 (+ p1 size) p2 (+ p2 size)
|
||||
success t)))
|
||||
(setq size (/ size 2)))))
|
||||
|
||||
(goto-char p1)
|
||||
(set-window-point w2 p2)
|
||||
(if (= (point) opoint1)
|
||||
(ding))))
|
466
lisp/emacs-lisp/cl-indent.el
Normal file
466
lisp/emacs-lisp/cl-indent.el
Normal file
@ -0,0 +1,466 @@
|
||||
;; Lisp mode, and its idiosyncratic commands.
|
||||
;; Copyright (C) 1987 Free Software Foundation, Inc.
|
||||
;; Written by Richard Mlynarik July 1987
|
||||
|
||||
;; This file is part of GNU Emacs.
|
||||
|
||||
;; GNU Emacs is free software; you can redistribute it and/or modify
|
||||
;; it under the terms of the GNU General Public License as published by
|
||||
;; the Free Software Foundation; either version 1, or (at your option)
|
||||
;; any later version.
|
||||
|
||||
;; GNU Emacs is distributed in the hope that it will be useful,
|
||||
;; but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
;; GNU General Public License for more details.
|
||||
|
||||
;; You should have received a copy of the GNU General Public License
|
||||
;; along with GNU Emacs; see the file COPYING. If not, write to
|
||||
;; the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.
|
||||
|
||||
;;>> TODO
|
||||
;; :foo
|
||||
;; bar
|
||||
;; :baz
|
||||
;; zap
|
||||
;; &key (like &body)??
|
||||
|
||||
;; &rest 1 in lambda-lists doesn't work
|
||||
;; -- really want (foo bar
|
||||
;; baz)
|
||||
;; not (foo bar
|
||||
;; baz)
|
||||
;; Need something better than &rest for such cases
|
||||
|
||||
|
||||
;;; Hairy lisp indentation.
|
||||
|
||||
(defvar lisp-indent-maximum-backtracking 3
|
||||
"*Maximum depth to backtrack out from a sublist for structured indentation.
|
||||
If this variable is 0, no backtracking will occur and forms such as flet
|
||||
may not be correctly indented.")
|
||||
|
||||
(defvar lisp-tag-indentation 1
|
||||
"*Indentation of tags relative to containing list.
|
||||
This variable is used by the function `lisp-indent-tagbody'.")
|
||||
|
||||
(defvar lisp-tag-body-indentation 3
|
||||
"*Indentation of non-tagged lines relative to containing list.
|
||||
This variable is used by the function `lisp-indent-tagbody' to indent normal
|
||||
lines (lines without tags).
|
||||
The indentation is relative to the indentation of the parenthesis enclosing
|
||||
the special form. If the value is t, the body of tags will be indented
|
||||
as a block at the same indentation as the first s-expression following
|
||||
the tag. In this case, any forms before the first tag are indented
|
||||
by `lisp-body-indent'.")
|
||||
|
||||
|
||||
;;;###autoload
|
||||
(defun common-lisp-indent-function (indent-point state)
|
||||
(let ((normal-indent (current-column)))
|
||||
;; Walk up list levels until we see something
|
||||
;; which does special things with subforms.
|
||||
(let ((depth 0)
|
||||
;; Path describes the position of point in terms of
|
||||
;; list-structure with respect to contining lists.
|
||||
;; `foo' has a path of (0 4 1) in `((a b c (d foo) f) g)'
|
||||
(path ())
|
||||
;; set non-nil when somebody works out the indentation to use
|
||||
calculated
|
||||
(last-point indent-point)
|
||||
;; the position of the open-paren of the innermost containing list
|
||||
(containing-form-start (elt state 1))
|
||||
;; the column of the above
|
||||
sexp-column)
|
||||
;; Move to start of innermost containing list
|
||||
(goto-char containing-form-start)
|
||||
(setq sexp-column (current-column))
|
||||
;; Look over successively less-deep containing forms
|
||||
(while (and (not calculated)
|
||||
(< depth lisp-indent-maximum-backtracking))
|
||||
(let ((containing-sexp (point)))
|
||||
(forward-char 1)
|
||||
(parse-partial-sexp (point) indent-point 1 t)
|
||||
;; Move to the car of the relevant containing form
|
||||
(let (tem function method)
|
||||
(if (not (looking-at "\\sw\\|\\s_"))
|
||||
;; This form doesn't seem to start with a symbol
|
||||
(setq function nil method nil)
|
||||
(setq tem (point))
|
||||
(forward-sexp 1)
|
||||
(setq function (downcase (buffer-substring tem (point))))
|
||||
(goto-char tem)
|
||||
(setq tem (intern-soft function)
|
||||
method (get tem 'common-lisp-indent-function))
|
||||
(cond ((and (null method)
|
||||
(string-match ":[^:]+" function))
|
||||
;; The pleblisp package feature
|
||||
(setq function (substring function
|
||||
(1+ (match-beginning 0)))
|
||||
method (get (intern-soft function)
|
||||
'common-lisp-indent-function)))
|
||||
((and (null method))
|
||||
;; backwards compatibility
|
||||
(setq method (get tem 'lisp-indent-function)))))
|
||||
(let ((n 0))
|
||||
;; How far into the containing form is the current form?
|
||||
(if (< (point) indent-point)
|
||||
(while (condition-case ()
|
||||
(progn
|
||||
(forward-sexp 1)
|
||||
(if (>= (point) indent-point)
|
||||
nil
|
||||
(parse-partial-sexp (point)
|
||||
indent-point 1 t)
|
||||
(setq n (1+ n))
|
||||
t))
|
||||
(error nil))))
|
||||
(setq path (cons n path)))
|
||||
|
||||
;; backwards compatibility.
|
||||
(cond ((null function))
|
||||
((null method)
|
||||
(if (null (cdr path))
|
||||
;; (package prefix was stripped off above)
|
||||
(setq method (cond ((string-match "\\`def"
|
||||
function)
|
||||
'(4 (&whole 4 &rest 1) &body))
|
||||
((string-match "\\`\\(with\\|do\\)-"
|
||||
function)
|
||||
'(4 &body))))))
|
||||
;; backwards compatibility. Bletch.
|
||||
((eq method 'defun)
|
||||
(setq method '(4 (&whole 4 &rest 1) &body))))
|
||||
|
||||
(cond ((and (memq (char-after (1- containing-sexp)) '(?\' ?\`))
|
||||
(not (eql (char-after (- containing-sexp 2)) ?\#)))
|
||||
;; No indentation for "'(...)" elements
|
||||
(setq calculated (1+ sexp-column)))
|
||||
((or (eql (char-after (1- containing-sexp)) ?\,)
|
||||
(and (eql (char-after (1- containing-sexp)) ?\@)
|
||||
(eql (char-after (- containing-sexp 2)) ?\,)))
|
||||
;; ",(...)" or ",@(...)"
|
||||
(setq calculated normal-indent))
|
||||
((eql (char-after (1- containing-sexp)) ?\#)
|
||||
;; "#(...)"
|
||||
(setq calculated (1+ sexp-column)))
|
||||
((null method))
|
||||
((integerp method)
|
||||
;; convenient top-level hack.
|
||||
;; (also compatible with lisp-indent-function)
|
||||
;; The number specifies how many `distinguished'
|
||||
;; forms there are before the body starts
|
||||
;; Equivalent to (4 4 ... &body)
|
||||
(setq calculated (cond ((cdr path)
|
||||
normal-indent)
|
||||
((<= (car path) method)
|
||||
;; `distinguished' form
|
||||
(list (+ sexp-column 4)
|
||||
containing-form-start))
|
||||
((= (car path) (1+ method))
|
||||
;; first body form.
|
||||
(+ sexp-column lisp-body-indent))
|
||||
(t
|
||||
;; other body form
|
||||
normal-indent))))
|
||||
((symbolp method)
|
||||
(setq calculated (funcall method
|
||||
path state indent-point
|
||||
sexp-column normal-indent)))
|
||||
(t
|
||||
(setq calculated (lisp-indent-259
|
||||
method path state indent-point
|
||||
sexp-column normal-indent)))))
|
||||
(goto-char containing-sexp)
|
||||
(setq last-point containing-sexp)
|
||||
(if (not calculated)
|
||||
(condition-case ()
|
||||
(progn (backward-up-list 1)
|
||||
(setq depth (1+ depth)))
|
||||
(error (setq depth lisp-indent-maximum-backtracking))))))
|
||||
calculated)))
|
||||
|
||||
|
||||
(defun lisp-indent-report-bad-format (m)
|
||||
(error "%s has a badly-formed %s property: %s"
|
||||
;; Love those free variable references!!
|
||||
function 'common-lisp-indent-function m))
|
||||
|
||||
;; Blame the crufty control structure on dynamic scoping
|
||||
;; -- not on me!
|
||||
(defun lisp-indent-259 (method path state indent-point
|
||||
sexp-column normal-indent)
|
||||
(catch 'exit
|
||||
(let ((p path)
|
||||
(containing-form-start (elt state 1))
|
||||
n tem tail)
|
||||
;; Isn't tail-recursion wonderful?
|
||||
(while p
|
||||
;; This while loop is for destructuring.
|
||||
;; p is set to (cdr p) each iteration.
|
||||
(if (not (consp method)) (lisp-indent-report-bad-format method))
|
||||
(setq n (1- (car p))
|
||||
p (cdr p)
|
||||
tail nil)
|
||||
(while n
|
||||
;; This while loop is for advancing along a method
|
||||
;; until the relevant (possibly &rest/&body) pattern
|
||||
;; is reached.
|
||||
;; n is set to (1- n) and method to (cdr method)
|
||||
;; each iteration.
|
||||
(setq tem (car method))
|
||||
|
||||
(or (eq tem 'nil) ;default indentation
|
||||
; (eq tem '&lambda) ;abbrev for (&whole 4 (&rest 1))
|
||||
(and (eq tem '&body) (null (cdr method)))
|
||||
(and (eq tem '&rest)
|
||||
(consp (cdr method)) (null (cdr (cdr method))))
|
||||
(integerp tem) ;explicit indentation specified
|
||||
(and (consp tem) ;destructuring
|
||||
(eq (car tem) '&whole)
|
||||
(or (symbolp (car (cdr tem)))
|
||||
(integerp (car (cdr tem)))))
|
||||
(and (symbolp tem) ;a function to call to do the work.
|
||||
(null (cdr method)))
|
||||
(lisp-indent-report-bad-format method))
|
||||
|
||||
(cond ((and tail (not (consp tem)))
|
||||
;; indent tail of &rest in same way as first elt of rest
|
||||
(throw 'exit normal-indent))
|
||||
((eq tem '&body)
|
||||
;; &body means (&rest <lisp-body-indent>)
|
||||
(throw 'exit
|
||||
(if (and (= n 0) ;first body form
|
||||
(null p)) ;not in subforms
|
||||
(+ sexp-column
|
||||
lisp-body-indent)
|
||||
normal-indent)))
|
||||
((eq tem '&rest)
|
||||
;; this pattern holds for all remaining forms
|
||||
(setq tail (> n 0)
|
||||
n 0
|
||||
method (cdr method)))
|
||||
((> n 0)
|
||||
;; try next element of pattern
|
||||
(setq n (1- n)
|
||||
method (cdr method))
|
||||
(if (< n 0)
|
||||
;; Too few elements in pattern.
|
||||
(throw 'exit normal-indent)))
|
||||
((eq tem 'nil)
|
||||
(throw 'exit (list normal-indent containing-form-start)))
|
||||
; ((eq tem '&lambda)
|
||||
; ;; abbrev for (&whole 4 &rest 1)
|
||||
; (throw 'exit
|
||||
; (cond ((null p)
|
||||
; (list (+ sexp-column 4) containing-form-start))
|
||||
; ((null (cdr p))
|
||||
; (+ sexp-column 1))
|
||||
; (t normal-indent))))
|
||||
((integerp tem)
|
||||
(throw 'exit
|
||||
(if (null p) ;not in subforms
|
||||
(list (+ sexp-column tem) containing-form-start)
|
||||
normal-indent)))
|
||||
((symbolp tem) ;a function to call
|
||||
(throw 'exit
|
||||
(funcall tem path state indent-point
|
||||
sexp-column normal-indent)))
|
||||
(t
|
||||
;; must be a destructing frob
|
||||
(if (not (null p))
|
||||
;; descend
|
||||
(setq method (cdr (cdr tem))
|
||||
n nil)
|
||||
(setq tem (car (cdr tem)))
|
||||
(throw 'exit
|
||||
(cond (tail
|
||||
normal-indent)
|
||||
((eq tem 'nil)
|
||||
(list normal-indent
|
||||
containing-form-start))
|
||||
((integerp tem)
|
||||
(list (+ sexp-column tem)
|
||||
containing-form-start))
|
||||
(t
|
||||
(funcall tem path state indent-point
|
||||
sexp-column normal-indent))))))))))))
|
||||
|
||||
(defun lisp-indent-tagbody (path state indent-point sexp-column normal-indent)
|
||||
(if (not (null (cdr path)))
|
||||
normal-indent
|
||||
(save-excursion
|
||||
(goto-char indent-point)
|
||||
(beginning-of-line)
|
||||
(skip-chars-forward " \t")
|
||||
(list (cond ((looking-at "\\sw\\|\\s_")
|
||||
;; a tagbody tag
|
||||
(+ sexp-column lisp-tag-indentation))
|
||||
((integerp lisp-tag-body-indentation)
|
||||
(+ sexp-column lisp-tag-body-indentation))
|
||||
((eq lisp-tag-body-indentation 't)
|
||||
(condition-case ()
|
||||
(progn (backward-sexp 1) (current-column))
|
||||
(error (1+ sexp-column))))
|
||||
(t (+ sexp-column lisp-body-indent)))
|
||||
; (cond ((integerp lisp-tag-body-indentation)
|
||||
; (+ sexp-column lisp-tag-body-indentation))
|
||||
; ((eq lisp-tag-body-indentation 't)
|
||||
; normal-indent)
|
||||
; (t
|
||||
; (+ sexp-column lisp-body-indent)))
|
||||
(elt state 1)
|
||||
))))
|
||||
|
||||
(defun lisp-indent-do (path state indent-point sexp-column normal-indent)
|
||||
(if (>= (car path) 3)
|
||||
(let ((lisp-tag-body-indentation lisp-body-indent))
|
||||
(funcall (function lisp-indent-tagbody)
|
||||
path state indent-point sexp-column normal-indent))
|
||||
(funcall (function lisp-indent-259)
|
||||
'((&whole nil &rest
|
||||
;; the following causes wierd indentation
|
||||
;;(&whole 1 1 2 nil)
|
||||
)
|
||||
(&whole nil &rest 1))
|
||||
path state indent-point sexp-column normal-indent)))
|
||||
|
||||
(defun lisp-indent-function-lambda-hack (path state indent-point
|
||||
sexp-column normal-indent)
|
||||
;; indent (function (lambda () <newline> <body-forms>)) kludgily.
|
||||
(if (or (cdr path) ; wtf?
|
||||
(> (car path) 3))
|
||||
;; line up under previous body form
|
||||
normal-indent
|
||||
;; line up under function rather than under lambda in order to
|
||||
;; conserve horizontal space. (Which is what #' is for.)
|
||||
(condition-case ()
|
||||
(save-excursion
|
||||
(backward-up-list 2)
|
||||
(forward-char 1)
|
||||
(if (looking-at "\\(lisp:+\\)?function\\(\\Sw\\|\\S_\\)")
|
||||
(+ lisp-body-indent -1 (current-column))
|
||||
(+ sexp-column lisp-body-indent)))
|
||||
(error (+ sexp-column lisp-body-indent)))))
|
||||
|
||||
|
||||
(let ((l '((block 1)
|
||||
(catch 1)
|
||||
(case (4 &rest (&whole 2 &rest 1)))
|
||||
(ccase . case) (ecase . case)
|
||||
(typecase . case) (etypecase . case) (ctypecase . case)
|
||||
(catch 1)
|
||||
(cond (&rest (&whole 2 &rest 1)))
|
||||
(block 1)
|
||||
(defvar (4 2 2))
|
||||
(defconstant . defvar) (defparameter . defvar)
|
||||
(define-modify-macro
|
||||
(4 &body))
|
||||
(define-setf-method
|
||||
(4 (&whole 4 &rest 1) &body))
|
||||
(defsetf (4 (&whole 4 &rest 1) 4 &body))
|
||||
(defun (4 (&whole 4 &rest 1) &body))
|
||||
(defmacro . defun) (deftype . defun)
|
||||
(defstruct ((&whole 4 &rest (&whole 2 &rest 1))
|
||||
&rest (&whole 2 &rest 1)))
|
||||
(destructuring-bind
|
||||
((&whole 6 &rest 1) 4 &body))
|
||||
(do lisp-indent-do)
|
||||
(do* . do)
|
||||
(dolist ((&whole 4 2 1) &body))
|
||||
(dotimes . dolist)
|
||||
(eval-when 1)
|
||||
(flet ((&whole 4 &rest (&whole 1 (&whole 4 &rest 1) &body))
|
||||
&body))
|
||||
(labels . flet)
|
||||
(macrolet . flet)
|
||||
;; `else-body' style
|
||||
(if (nil nil &body))
|
||||
;; single-else style (then and else equally indented)
|
||||
(if (&rest nil))
|
||||
;(lambda ((&whole 4 &rest 1) &body))
|
||||
(lambda ((&whole 4 &rest 1)
|
||||
&rest lisp-indent-function-lambda-hack))
|
||||
(let ((&whole 4 &rest (&whole 1 1 2)) &body))
|
||||
(let* . let)
|
||||
(compiler-let . let) ;barf
|
||||
(locally 1)
|
||||
;(loop ...)
|
||||
(multiple-value-bind
|
||||
((&whole 6 &rest 1) 4 &body))
|
||||
(multiple-value-call
|
||||
(4 &body))
|
||||
(multiple-value-list 1)
|
||||
(multiple-value-prog1 1)
|
||||
(multiple-value-setq
|
||||
(4 2))
|
||||
;; Combines the worst features of BLOCK, LET and TAGBODY
|
||||
(prog ((&whole 4 &rest 1) &rest lisp-indent-tagbody))
|
||||
(prog* . prog)
|
||||
(prog1 1)
|
||||
(prog2 2)
|
||||
(progn 0)
|
||||
(progv (4 4 &body))
|
||||
(return 0)
|
||||
(return-from (nil &body))
|
||||
(tagbody lisp-indent-tagbody)
|
||||
(throw 1)
|
||||
(unless 1)
|
||||
(unwind-protect
|
||||
(5 &body))
|
||||
(when 1))))
|
||||
(while l
|
||||
(put (car (car l)) 'common-lisp-indent-function
|
||||
(if (symbolp (cdr (car l)))
|
||||
(get (cdr (car l)) 'common-lisp-indent-function)
|
||||
(car (cdr (car l)))))
|
||||
(setq l (cdr l))))
|
||||
|
||||
|
||||
;(defun foo (x)
|
||||
; (tagbody
|
||||
; foo
|
||||
; (bar)
|
||||
; baz
|
||||
; (when (losing)
|
||||
; (with-big-loser
|
||||
; (yow)
|
||||
; ((lambda ()
|
||||
; foo)
|
||||
; big)))
|
||||
; (flet ((foo (bar baz zap)
|
||||
; (zip))
|
||||
; (zot ()
|
||||
; quux))
|
||||
; (do ()
|
||||
; ((lose)
|
||||
; (foo 1))
|
||||
; (quux)
|
||||
; foo
|
||||
; (lose))
|
||||
; (cond ((x)
|
||||
; (win 1 2
|
||||
; (foo)))
|
||||
; (t
|
||||
; (lose
|
||||
; 3))))))
|
||||
|
||||
|
||||
;(put 'while 'common-lisp-indent-function 1)
|
||||
;(put 'defwrapper'common-lisp-indent-function ...)
|
||||
;(put 'def 'common-lisp-indent-function ...)
|
||||
;(put 'defflavor 'common-lisp-indent-function ...)
|
||||
;(put 'defsubst 'common-lisp-indent-function ...)
|
||||
|
||||
;(put 'with-restart 'common-lisp-indent-function '((1 4 ((* 1))) (2 &body)))
|
||||
;(put 'restart-case 'common-lisp-indent-function '((1 4) (* 2 ((0 1) (* 1)))))
|
||||
;(put 'define-condition 'common-lisp-indent-function '((1 6) (2 6 ((* 1))) (3 4 ((* 1))) (4 &body)))
|
||||
;(put 'with-condition-handler 'common-lisp-indent-function '((1 4 ((* 1))) (2 &body)))
|
||||
;(put 'condition-case 'common-lisp-indent-function '((1 4) (* 2 ((0 1) (1 3) (2 &body)))))
|
||||
|
||||
|
||||
;;;; Turn it on.
|
||||
;(setq lisp-indent-function 'common-lisp-indent-function)
|
||||
|
||||
;; To disable this stuff, (setq lisp-indent-function 'lisp-indent-function)
|
||||
|
6081
lisp/gnus.el
Normal file
6081
lisp/gnus.el
Normal file
File diff suppressed because it is too large
Load Diff
415
lisp/informat.el
Normal file
415
lisp/informat.el
Normal file
@ -0,0 +1,415 @@
|
||||
;; Info support functions package for Emacs
|
||||
;; Copyright (C) 1986 Free Software Foundation, Inc.
|
||||
|
||||
;; This file is part of GNU Emacs.
|
||||
|
||||
;; GNU Emacs is free software; you can redistribute it and/or modify
|
||||
;; it under the terms of the GNU General Public License as published by
|
||||
;; the Free Software Foundation; either version 1, or (at your option)
|
||||
;; any later version.
|
||||
|
||||
;; GNU Emacs is distributed in the hope that it will be useful,
|
||||
;; but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
;; GNU General Public License for more details.
|
||||
|
||||
;; You should have received a copy of the GNU General Public License
|
||||
;; along with GNU Emacs; see the file COPYING. If not, write to
|
||||
;; the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.
|
||||
|
||||
(require 'info)
|
||||
|
||||
;;;###autoload
|
||||
(defun Info-tagify ()
|
||||
"Create or update Info-file tag table in current buffer."
|
||||
(interactive)
|
||||
;; Save and restore point and restrictions.
|
||||
;; save-restrictions would not work
|
||||
;; because it records the old max relative to the end.
|
||||
;; We record it relative to the beginning.
|
||||
(message "Tagifying %s ..." (file-name-nondirectory (buffer-file-name)))
|
||||
(let ((omin (point-min))
|
||||
(omax (point-max))
|
||||
(nomax (= (point-max) (1+ (buffer-size))))
|
||||
(opoint (point)))
|
||||
(unwind-protect
|
||||
(progn
|
||||
(widen)
|
||||
(goto-char (point-min))
|
||||
(if (search-forward "\^_\nIndirect:\n" nil t)
|
||||
(message "Cannot tagify split info file")
|
||||
(let ((regexp "Node:[ \t]*\\([^,\n\t]\\)*[,\t\n]")
|
||||
(case-fold-search t)
|
||||
list)
|
||||
(while (search-forward "\n\^_" nil t)
|
||||
(forward-line 1)
|
||||
(let ((beg (point)))
|
||||
(forward-line 1)
|
||||
(if (re-search-backward regexp beg t)
|
||||
(setq list
|
||||
(cons (list (buffer-substring
|
||||
(match-beginning 1)
|
||||
(match-end 1))
|
||||
beg)
|
||||
list)))))
|
||||
(goto-char (point-max))
|
||||
(forward-line -8)
|
||||
(let ((buffer-read-only nil))
|
||||
(if (search-forward "\^_\nEnd tag table\n" nil t)
|
||||
(let ((end (point)))
|
||||
(search-backward "\nTag table:\n")
|
||||
(beginning-of-line)
|
||||
(delete-region (point) end)))
|
||||
(goto-char (point-max))
|
||||
(insert "\^_\f\nTag table:\n")
|
||||
(move-marker Info-tag-table-marker (point))
|
||||
(setq list (nreverse list))
|
||||
(while list
|
||||
(insert "Node: " (car (car list)) ?\177)
|
||||
(princ (car (cdr (car list))) (current-buffer))
|
||||
(insert ?\n)
|
||||
(setq list (cdr list)))
|
||||
(insert "\^_\nEnd tag table\n")))))
|
||||
(goto-char opoint)
|
||||
(narrow-to-region omin (if nomax (1+ (buffer-size))
|
||||
(min omax (point-max))))))
|
||||
(message "Tagifying %s ... done" (file-name-nondirectory (buffer-file-name))))
|
||||
|
||||
;;;###autoload
|
||||
(defun Info-split ()
|
||||
"Split an info file into an indirect file plus bounded-size subfiles.
|
||||
Each subfile will be up to 50,000 characters plus one node.
|
||||
|
||||
To use this command, first visit a large Info file that has a tag
|
||||
table. The buffer is modified into a (small) indirect info file which
|
||||
should be saved in place of the original visited file.
|
||||
|
||||
The subfiles are written in the same directory the original file is
|
||||
in, with names generated by appending `-' and a number to the original
|
||||
file name. The indirect file still functions as an Info file, but it
|
||||
contains just the tag table and a directory of subfiles."
|
||||
|
||||
(interactive)
|
||||
(if (< (buffer-size) 70000)
|
||||
(error "This is too small to be worth splitting"))
|
||||
(goto-char (point-min))
|
||||
(search-forward "\^_")
|
||||
(forward-char -1)
|
||||
(let ((start (point))
|
||||
(chars-deleted 0)
|
||||
subfiles
|
||||
(subfile-number 1)
|
||||
(case-fold-search t)
|
||||
(filename (file-name-sans-versions buffer-file-name)))
|
||||
(goto-char (point-max))
|
||||
(forward-line -8)
|
||||
(setq buffer-read-only nil)
|
||||
(or (search-forward "\^_\nEnd tag table\n" nil t)
|
||||
(error "Tag table required; use M-x Info-tagify"))
|
||||
(search-backward "\nTag table:\n")
|
||||
(if (looking-at "\nTag table:\n\^_")
|
||||
(error "Tag table is just a skeleton; use M-x Info-tagify"))
|
||||
(beginning-of-line)
|
||||
(forward-char 1)
|
||||
(save-restriction
|
||||
(narrow-to-region (point-min) (point))
|
||||
(goto-char (point-min))
|
||||
(while (< (1+ (point)) (point-max))
|
||||
(goto-char (min (+ (point) 50000) (point-max)))
|
||||
(search-forward "\^_" nil 'move)
|
||||
(setq subfiles
|
||||
(cons (list (+ start chars-deleted)
|
||||
(concat (file-name-nondirectory filename)
|
||||
(format "-%d" subfile-number)))
|
||||
subfiles))
|
||||
;; Put a newline at end of split file, to make Unix happier.
|
||||
(insert "\n")
|
||||
(write-region (point-min) (point)
|
||||
(concat filename (format "-%d" subfile-number)))
|
||||
(delete-region (1- (point)) (point))
|
||||
;; Back up over the final ^_.
|
||||
(forward-char -1)
|
||||
(setq chars-deleted (+ chars-deleted (- (point) start)))
|
||||
(delete-region start (point))
|
||||
(setq subfile-number (1+ subfile-number))))
|
||||
(while subfiles
|
||||
(goto-char start)
|
||||
(insert (nth 1 (car subfiles))
|
||||
(format ": %d" (car (car subfiles)))
|
||||
"\n")
|
||||
(setq subfiles (cdr subfiles)))
|
||||
(goto-char start)
|
||||
(insert "\^_\nIndirect:\n")
|
||||
(search-forward "\nTag Table:\n")
|
||||
(insert "(Indirect)\n")))
|
||||
|
||||
;;;###autoload
|
||||
(defun Info-validate ()
|
||||
"Check current buffer for validity as an Info file.
|
||||
Check that every node pointer points to an existing node."
|
||||
(interactive)
|
||||
(save-excursion
|
||||
(save-restriction
|
||||
(widen)
|
||||
(goto-char (point-min))
|
||||
(if (search-forward "\nTag table:\n(Indirect)\n" nil t)
|
||||
(error "Don't yet know how to validate indirect info files: \"%s\""
|
||||
(buffer-name (current-buffer))))
|
||||
(goto-char (point-min))
|
||||
(let ((allnodes '(("*")))
|
||||
(regexp "Node:[ \t]*\\([^,\n\t]*\\)[,\t\n]")
|
||||
(case-fold-search t)
|
||||
(tags-losing nil)
|
||||
(lossages ()))
|
||||
(while (search-forward "\n\^_" nil t)
|
||||
(forward-line 1)
|
||||
(let ((beg (point)))
|
||||
(forward-line 1)
|
||||
(if (re-search-backward regexp beg t)
|
||||
(let ((name (downcase
|
||||
(buffer-substring
|
||||
(match-beginning 1)
|
||||
(progn
|
||||
(goto-char (match-end 1))
|
||||
(skip-chars-backward " \t")
|
||||
(point))))))
|
||||
(if (assoc name allnodes)
|
||||
(setq lossages
|
||||
(cons (list name "Duplicate node-name" nil)
|
||||
lossages))
|
||||
(setq allnodes
|
||||
(cons (list name
|
||||
(progn
|
||||
(end-of-line)
|
||||
(and (re-search-backward
|
||||
"prev[ious]*:" beg t)
|
||||
(progn
|
||||
(goto-char (match-end 0))
|
||||
(downcase
|
||||
(Info-following-node-name)))))
|
||||
beg)
|
||||
allnodes)))))))
|
||||
(goto-char (point-min))
|
||||
(while (search-forward "\n\^_" nil t)
|
||||
(forward-line 1)
|
||||
(let ((beg (point))
|
||||
thisnode next)
|
||||
(forward-line 1)
|
||||
(if (re-search-backward regexp beg t)
|
||||
(save-restriction
|
||||
(search-forward "\n\^_" nil 'move)
|
||||
(narrow-to-region beg (point))
|
||||
(setq thisnode (downcase
|
||||
(buffer-substring
|
||||
(match-beginning 1)
|
||||
(progn
|
||||
(goto-char (match-end 1))
|
||||
(skip-chars-backward " \t")
|
||||
(point)))))
|
||||
(end-of-line)
|
||||
(and (search-backward "next:" nil t)
|
||||
(setq next (Info-validate-node-name "invalid Next"))
|
||||
(assoc next allnodes)
|
||||
(if (equal (car (cdr (assoc next allnodes)))
|
||||
thisnode)
|
||||
;; allow multiple `next' pointers to one node
|
||||
(let ((tem lossages))
|
||||
(while tem
|
||||
(if (and (equal (car (cdr (car tem)))
|
||||
"should have Previous")
|
||||
(equal (car (car tem))
|
||||
next))
|
||||
(setq lossages (delq (car tem) lossages)))
|
||||
(setq tem (cdr tem))))
|
||||
(setq lossages
|
||||
(cons (list next
|
||||
"should have Previous"
|
||||
thisnode)
|
||||
lossages))))
|
||||
(end-of-line)
|
||||
(if (re-search-backward "prev[ious]*:" nil t)
|
||||
(Info-validate-node-name "invalid Previous"))
|
||||
(end-of-line)
|
||||
(if (search-backward "up:" nil t)
|
||||
(Info-validate-node-name "invalid Up"))
|
||||
(if (re-search-forward "\n* Menu:" nil t)
|
||||
(while (re-search-forward "\n\\* " nil t)
|
||||
(Info-validate-node-name
|
||||
(concat "invalid menu item "
|
||||
(buffer-substring (point)
|
||||
(save-excursion
|
||||
(skip-chars-forward "^:")
|
||||
(point))))
|
||||
(Info-extract-menu-node-name))))
|
||||
(goto-char (point-min))
|
||||
(while (re-search-forward "\\*note[ \n]*[^:\t]*:" nil t)
|
||||
(goto-char (+ (match-beginning 0) 5))
|
||||
(skip-chars-forward " \n")
|
||||
(Info-validate-node-name
|
||||
(concat "invalid reference "
|
||||
(buffer-substring (point)
|
||||
(save-excursion
|
||||
(skip-chars-forward "^:")
|
||||
(point))))
|
||||
(Info-extract-menu-node-name "Bad format cross-reference")))))))
|
||||
(setq tags-losing (not (Info-validate-tags-table)))
|
||||
(if (or lossages tags-losing)
|
||||
(with-output-to-temp-buffer " *problems in info file*"
|
||||
(while lossages
|
||||
(princ "In node \"")
|
||||
(princ (car (car lossages)))
|
||||
(princ "\", ")
|
||||
(let ((tem (nth 1 (car lossages))))
|
||||
(cond ((string-match "\n" tem)
|
||||
(princ (substring tem 0 (match-beginning 0)))
|
||||
(princ "..."))
|
||||
(t
|
||||
(princ tem))))
|
||||
(if (nth 2 (car lossages))
|
||||
(progn
|
||||
(princ ": ")
|
||||
(let ((tem (nth 2 (car lossages))))
|
||||
(cond ((string-match "\n" tem)
|
||||
(princ (substring tem 0 (match-beginning 0)))
|
||||
(princ "..."))
|
||||
(t
|
||||
(princ tem))))))
|
||||
(terpri)
|
||||
(setq lossages (cdr lossages)))
|
||||
(if tags-losing (princ "\nTags table must be recomputed\n")))
|
||||
;; Here if info file is valid.
|
||||
;; If we already made a list of problems, clear it out.
|
||||
(save-excursion
|
||||
(if (get-buffer " *problems in info file*")
|
||||
(progn
|
||||
(set-buffer " *problems in info file*")
|
||||
(kill-buffer (current-buffer)))))
|
||||
(message "File appears valid"))))))
|
||||
|
||||
(defun Info-validate-node-name (kind &optional name)
|
||||
(if name
|
||||
nil
|
||||
(goto-char (match-end 0))
|
||||
(skip-chars-forward " \t")
|
||||
(if (= (following-char) ?\()
|
||||
nil
|
||||
(setq name
|
||||
(buffer-substring
|
||||
(point)
|
||||
(progn
|
||||
(skip-chars-forward "^,\t\n")
|
||||
(skip-chars-backward " ")
|
||||
(point))))))
|
||||
(if (null name)
|
||||
nil
|
||||
(setq name (downcase name))
|
||||
(or (and (> (length name) 0) (= (aref name 0) ?\())
|
||||
(assoc name allnodes)
|
||||
(setq lossages
|
||||
(cons (list thisnode kind name) lossages))))
|
||||
name)
|
||||
|
||||
(defun Info-validate-tags-table ()
|
||||
(goto-char (point-min))
|
||||
(if (not (search-forward "\^_\nEnd tag table\n" nil t))
|
||||
t
|
||||
(not (catch 'losing
|
||||
(let* ((end (match-beginning 0))
|
||||
(start (progn (search-backward "\nTag table:\n")
|
||||
(1- (match-end 0))))
|
||||
tem)
|
||||
(setq tem allnodes)
|
||||
(while tem
|
||||
(goto-char start)
|
||||
(or (equal (car (car tem)) "*")
|
||||
(search-forward (concat "Node: "
|
||||
(car (car tem))
|
||||
"\177")
|
||||
end t)
|
||||
(throw 'losing 'x))
|
||||
(setq tem (cdr tem)))
|
||||
(goto-char (1+ start))
|
||||
(while (looking-at ".*Node: \\(.*\\)\177\\([0-9]+\\)$")
|
||||
(setq tem (downcase (buffer-substring
|
||||
(match-beginning 1)
|
||||
(match-end 1))))
|
||||
(setq tem (assoc tem allnodes))
|
||||
(if (or (not tem)
|
||||
(< 1000 (progn
|
||||
(goto-char (match-beginning 2))
|
||||
(setq tem (- (car (cdr (cdr tem)))
|
||||
(read (current-buffer))))
|
||||
(if (> tem 0) tem (- tem)))))
|
||||
(throw 'losing 'y)))
|
||||
(forward-line 1))
|
||||
(or (looking-at "End tag table\n")
|
||||
(throw 'losing 'z))
|
||||
nil))))
|
||||
|
||||
;;;###autoload
|
||||
(defun batch-info-validate ()
|
||||
"Runs `Info-validate' on the files remaining on the command line.
|
||||
Must be used only with -batch, and kills Emacs on completion.
|
||||
Each file will be processed even if an error occurred previously.
|
||||
For example, invoke \"emacs -batch -f batch-info-validate $info/ ~/*.info\""
|
||||
(if (not noninteractive)
|
||||
(error "batch-info-validate may only be used -batch."))
|
||||
(let ((version-control t)
|
||||
(auto-save-default nil)
|
||||
(find-file-run-dired nil)
|
||||
(kept-old-versions 259259)
|
||||
(kept-new-versions 259259))
|
||||
(let ((error 0)
|
||||
file
|
||||
(files ()))
|
||||
(while command-line-args-left
|
||||
(setq file (expand-file-name (car command-line-args-left)))
|
||||
(cond ((not (file-exists-p file))
|
||||
(message ">> %s does not exist!" file)
|
||||
(setq error 1
|
||||
command-line-args-left (cdr command-line-args-left)))
|
||||
((file-directory-p file)
|
||||
(setq command-line-args-left (nconc (directory-files file)
|
||||
(cdr command-line-args-left))))
|
||||
(t
|
||||
(setq files (cons file files)
|
||||
command-line-args-left (cdr command-line-args-left)))))
|
||||
(while files
|
||||
(setq file (car files)
|
||||
files (cdr files))
|
||||
(let ((lose nil))
|
||||
(condition-case err
|
||||
(progn
|
||||
(if buffer-file-name (kill-buffer (current-buffer)))
|
||||
(find-file file)
|
||||
(buffer-disable-undo (current-buffer))
|
||||
(set-buffer-modified-p nil)
|
||||
(fundamental-mode)
|
||||
(let ((case-fold-search nil))
|
||||
(goto-char (point-max))
|
||||
(cond ((search-backward "\n\^_\^L\nTag table:\n" nil t)
|
||||
(message "%s already tagified" file))
|
||||
((< (point-max) 30000)
|
||||
(message "%s too small to bother tagifying" file))
|
||||
(t
|
||||
(Info-tagify file))))
|
||||
(let ((loss-name " *problems in info file*"))
|
||||
(message "Checking validity of info file %s..." file)
|
||||
(if (get-buffer loss-name)
|
||||
(kill-buffer loss-name))
|
||||
(Info-validate)
|
||||
(if (not (get-buffer loss-name))
|
||||
nil ;(message "Checking validity of info file %s... OK" file)
|
||||
(message "----------------------------------------------------------------------")
|
||||
(message ">> PROBLEMS IN INFO FILE %s" file)
|
||||
(save-excursion
|
||||
(set-buffer loss-name)
|
||||
(princ (buffer-substring (point-min) (point-max))))
|
||||
(message "----------------------------------------------------------------------")
|
||||
(setq error 1 lose t)))
|
||||
(if (and (buffer-modified-p)
|
||||
(not lose))
|
||||
(progn (message "Saving modified %s" file)
|
||||
(save-buffer))))
|
||||
(error (message ">> Error: %s" (prin1-to-string err))))))
|
||||
(kill-emacs error))))
|
83
lisp/progmodes/awk-mode.el
Normal file
83
lisp/progmodes/awk-mode.el
Normal file
@ -0,0 +1,83 @@
|
||||
;; C code editing commands for Emacs
|
||||
;; Copyright (C) 1988 Free Software Foundation, Inc.
|
||||
|
||||
;; This file is part of GNU Emacs.
|
||||
|
||||
;; GNU Emacs is free software; you can redistribute it and/or modify
|
||||
;; it under the terms of the GNU General Public License as published by
|
||||
;; the Free Software Foundation; either version 1, or (at your option)
|
||||
;; any later version.
|
||||
|
||||
;; GNU Emacs is distributed in the hope that it will be useful,
|
||||
;; but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
;; GNU General Public License for more details.
|
||||
|
||||
;; You should have received a copy of the GNU General Public License
|
||||
;; along with GNU Emacs; see the file COPYING. If not, write to
|
||||
;; the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.
|
||||
|
||||
|
||||
(defvar awk-mode-syntax-table nil
|
||||
"Syntax table in use in Awk-mode buffers.")
|
||||
|
||||
(if awk-mode-syntax-table
|
||||
()
|
||||
(setq awk-mode-syntax-table (make-syntax-table))
|
||||
(modify-syntax-entry ?\\ "\\" awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?\n "> " emacs-lisp-mode-syntax-table)
|
||||
(modify-syntax-entry ?\f "> " emacs-lisp-mode-syntax-table)
|
||||
(modify-syntax-entry ?\# "< " emacs-lisp-mode-syntax-table)
|
||||
(modify-syntax-entry ?/ "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?* "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?+ "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?- "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?= "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?% "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?< "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?> "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?& "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?| "." awk-mode-syntax-table)
|
||||
(modify-syntax-entry ?\' "\"" awk-mode-syntax-table))
|
||||
|
||||
(defvar awk-mode-abbrev-table nil
|
||||
"Abbrev table in use in Awk-mode buffers.")
|
||||
(define-abbrev-table 'awk-mode-abbrev-table ())
|
||||
|
||||
;;;###autoload
|
||||
(defun awk-mode ()
|
||||
"Major mode for editing AWK code.
|
||||
This is much like C mode except for the syntax of comments. It uses
|
||||
the same keymap as C mode and has the same variables for customizing
|
||||
indentation. It has its own abbrev table and its own syntax table.
|
||||
|
||||
Turning on AWK mode calls the value of the variable `awk-mode-hook'
|
||||
with no args, if that value is non-nil."
|
||||
(interactive)
|
||||
(kill-all-local-variables)
|
||||
(use-local-map c-mode-map)
|
||||
(setq major-mode 'awk-mode)
|
||||
(setq mode-name "AWK")
|
||||
(setq local-abbrev-table awk-mode-abbrev-table)
|
||||
(set-syntax-table awk-mode-syntax-table)
|
||||
(make-local-variable 'paragraph-start)
|
||||
(setq paragraph-start (concat "^$\\|" page-delimiter))
|
||||
(make-local-variable 'paragraph-separate)
|
||||
(setq paragraph-separate paragraph-start)
|
||||
(make-local-variable 'paragraph-ignore-fill-prefix)
|
||||
(setq paragraph-ignore-fill-prefix t)
|
||||
(make-local-variable 'indent-line-function)
|
||||
(setq indent-line-function 'awk-indent-line)
|
||||
(make-local-variable 'require-final-newline)
|
||||
(setq require-final-newline t)
|
||||
(make-local-variable 'comment-start)
|
||||
(setq comment-start "# ")
|
||||
(make-local-variable 'comment-end)
|
||||
(setq comment-end "")
|
||||
(make-local-variable 'comment-column)
|
||||
(setq comment-column 32)
|
||||
(make-local-variable 'comment-start-skip)
|
||||
(setq comment-start-skip "#+ *")
|
||||
(make-local-variable 'comment-indent-hook)
|
||||
(setq comment-indent-hook 'c-comment-indent)
|
||||
(run-hooks 'awk-mode-hook))
|
966
lisp/progmodes/cplus-md.el
Normal file
966
lisp/progmodes/cplus-md.el
Normal file
@ -0,0 +1,966 @@
|
||||
;; C++ code editing commands for Emacs
|
||||
;; 1987 Dave Detlefs (dld@cs.cmu.edu)
|
||||
;; and Stewart Clamen (clamen@cs.cmu.edu).
|
||||
;; Done by fairly faithful modification of:
|
||||
;; c-mode.el, Copyright (C) 1985 Richard M. Stallman.
|
||||
;;
|
||||
;; Feb, 1990 (Dave Detlefs, dld@cs.cmu.edu)
|
||||
;; Fixed electric-c++-terminator to handle double colons, at the
|
||||
;; request of John Hagerman.
|
||||
;;
|
||||
;; Jan, 1990 (Doug Lea, dl@oswego.edu)
|
||||
;; Replaced c++-comment-region and c++-uncomment-region with
|
||||
;; versions from Igor Metz that avoid potential infinite loops.
|
||||
;;
|
||||
;; Oct, 1989 (Dave Detlefs, dld@cs.cmu.edu)
|
||||
;; Added contribution from Igor Metz <metz@iam.unibe.ch>:
|
||||
;; functions c++-comment-region and c++-uncomment-region and
|
||||
;; corresponding key-binding.
|
||||
;; Also fixed bug in indentation of second line after an empty
|
||||
;; arglist with empty-arglist non-null.
|
||||
;;
|
||||
;; Sept, 1989 (Glen Ditchfield, gjditchfield@violet.uwaterloo.ca):
|
||||
;; Textual changes to more closely imitate Emacs 18.55's c-mode.
|
||||
;; Fixed handling of "default:", where ":" was the last character in the
|
||||
;; buffer. Fixed indentation of comments starting in column 0, and when
|
||||
;; previous line contained more than one comment start string. Fixed
|
||||
;; handling of "friend class".
|
||||
;;
|
||||
;; Aug 7, 1989; John Hagerman (hagerman@ece.cmu.edu):
|
||||
;; Changed calculate-c++-indent to handle member initializations
|
||||
;; more flexibly. Two new variables are used to control behavior:
|
||||
;; c++-member-init-indent and c++-continued-member-init-offset.
|
||||
;; Note the assumption that member initializations and argument
|
||||
;; declarations are not mixed in one function definition.
|
||||
;;
|
||||
;; June 1989 (Dave Detlefs, dld@cs.cmu.edu)
|
||||
;; Fixed calculate-c++-indent to handle continued lines ending in
|
||||
;; {'s. (I wasn't following C-mode closely enough, or C-mode
|
||||
;; changed.) Made ' a quote character, at the behest of someone
|
||||
;; whose mail I apparently deleted (if they send me mail I'll credit
|
||||
;; them here in a future revision.)
|
||||
;; Dan Weinreb (dlw@odi.com) pointed out that 'c++-mode successively
|
||||
;; bound c++-indent-exp and c++-indent-defun to ESC-^q. ESC-^q is
|
||||
;; now bound to c++-indent-exp, while, c++-indent-defun is invoked
|
||||
;; with ESC-^x.
|
||||
|
||||
;; February 1989 (Dave Detlefs, dld@cs.cmu.edu)
|
||||
;; Fixed some errors in c++-indent-defun, as pointed out by Sam
|
||||
;; Haradhvala (odi!sam@talcott.harvard.edu).
|
||||
;; October 1988 (Dave Detlefs, dld@cs.cmu.edu)
|
||||
;; It turns out I had only *thought* I had made
|
||||
;; beginning(end)-of-defun work. It should work better now -- you
|
||||
;; can either attempt to match defun headers "strongly," using a
|
||||
;; very complicated regexp, or "weakly," using a simple one. This
|
||||
;; is settable by a variable; the default is the cheaper weak
|
||||
;; method. (Stewart Clamen was intimately involved in this, too.)
|
||||
;;
|
||||
;; I made "'" *not* be a string delimiter, because that was causing
|
||||
;; comments containing contractions to ("// don't") to mess up paren
|
||||
;; balancing.
|
||||
;;
|
||||
;; I also incorporated another slight indentation fix from Glen
|
||||
;; Ditchfield.
|
||||
;;
|
||||
;; We hope this is will make into version 19 of gnu-emacs.
|
||||
;;
|
||||
;; September 1988: incorporated changes from Fred Calm at Schlumberger.
|
||||
;; Also, made beginning(end)-of-defun, indent-defun work.
|
||||
;;
|
||||
;; August 1987: incorporated changes done by Glen Ditchfield of Waterloo.
|
||||
|
||||
(defvar c++-mode-abbrev-table nil
|
||||
"Abbrev table used in C++ mode.")
|
||||
(define-abbrev-table 'c++-mode-abbrev-table ())
|
||||
|
||||
(defvar c++-mode-map ()
|
||||
"Keymap used in C++ mode.")
|
||||
(if c++-mode-map
|
||||
()
|
||||
(setq c++-mode-map (make-sparse-keymap))
|
||||
(define-key c++-mode-map "\C-j" 'reindent-then-newline-and-indent)
|
||||
(define-key c++-mode-map "{" 'electric-c++-brace)
|
||||
(define-key c++-mode-map "}" 'electric-c++-brace)
|
||||
(define-key c++-mode-map ";" 'electric-c++-semi)
|
||||
(define-key c++-mode-map "\e\C-h" 'mark-c-function)
|
||||
(define-key c++-mode-map "\e\C-q" 'indent-c++-exp)
|
||||
(define-key c++-mode-map "\177" 'backward-delete-char-untabify)
|
||||
(define-key c++-mode-map "\t" 'c++-indent-command)
|
||||
(define-key c++-mode-map "\C-c\C-i" 'c++-insert-header)
|
||||
(define-key c++-mode-map "\C-c\C-\\" 'c++-macroize-region)
|
||||
(define-key c++-mode-map "\C-c\C-c" 'c++-comment-region)
|
||||
(define-key c++-mode-map "\C-c\C-u" 'c++-uncomment-region)
|
||||
(define-key c++-mode-map "\e\C-a" 'c++-beginning-of-defun)
|
||||
(define-key c++-mode-map "\e\C-e" 'c++-end-of-defun)
|
||||
(define-key c++-mode-map "\e\C-x" 'c++-indent-defun))
|
||||
|
||||
(defvar c++-mode-syntax-table nil
|
||||
"Syntax table used in C++ mode.")
|
||||
|
||||
(if c++-mode-syntax-table
|
||||
()
|
||||
(setq c++-mode-syntax-table (copy-syntax-table c-mode-syntax-table))
|
||||
(modify-syntax-entry ?/ ". 12" c++-mode-syntax-table)
|
||||
(modify-syntax-entry ?\n ">" c++-mode-syntax-table)
|
||||
(modify-syntax-entry ?\' "." c++-mode-syntax-table))
|
||||
|
||||
(defvar c++-continued-member-init-offset nil
|
||||
"*Extra indent for continuation lines of member inits;
|
||||
NIL means to align with previous initializations rather than
|
||||
with the colon on the first line.")
|
||||
(defvar c++-member-init-indent 0
|
||||
"*Indentation level of member initializations in function declarations.")
|
||||
(defvar c++-friend-offset -4
|
||||
"*Offset of C++ friend class declarations relative to member declarations.")
|
||||
(defvar c++-electric-colon t
|
||||
"*If t, colon is an electric terminator.")
|
||||
(defvar c++-empty-arglist-indent nil
|
||||
"*Indicates how far to indent an line following an empty argument
|
||||
list. Nil indicates to just after the paren.")
|
||||
|
||||
|
||||
;;;###autoload
|
||||
(defun c++-mode ()
|
||||
"Major mode for editing C++ code. Very much like editing C code.
|
||||
Expression and list commands understand all C++ brackets.
|
||||
Tab at left margin indents for C++ code
|
||||
Comments are delimited with /* ... */ {or with // ... <newline>}
|
||||
Paragraphs are separated by blank lines only.
|
||||
Delete converts tabs to spaces as it moves back.
|
||||
\\{c++-mode-map}
|
||||
Variables controlling indentation style:
|
||||
c-tab-always-indent
|
||||
Non-nil means TAB in C mode should always reindent the current line,
|
||||
regardless of where in the line point is when the TAB command is used.
|
||||
Default is t.
|
||||
c-auto-newline
|
||||
Non-nil means automatically newline before and after braces,
|
||||
and after colons and semicolons, inserted in C code.
|
||||
c-indent-level
|
||||
Indentation of C statements within surrounding block.
|
||||
The surrounding block's indentation is the indentation
|
||||
of the line on which the open-brace appears.
|
||||
c-continued-statement-offset
|
||||
Extra indentation given to a substatement, such as the
|
||||
then-clause of an if or body of a while.
|
||||
c-continued-brace-offset
|
||||
Extra indentation given to a brace that starts a substatement.
|
||||
This is in addition to c-continued-statement-offset.
|
||||
c-brace-offset
|
||||
Extra indentation for line if it starts with an open brace.
|
||||
c-brace-imaginary-offset
|
||||
An open brace following other text is treated as if it were
|
||||
this far to the right of the start of its line.
|
||||
c-argdecl-indent
|
||||
Indentation level of declarations of C function arguments.
|
||||
c-label-offset
|
||||
Extra indentation for line that is a label, or case or ``default:'', or
|
||||
``public:'' or ``private:'', or ``protected:''.
|
||||
c++-electric-colon
|
||||
If non-nil at invocation of c++-mode (t is the default) colon electricly
|
||||
indents.
|
||||
c++-empty-arglist-indent
|
||||
If non-nil, a function declaration or invocation which ends a line with a
|
||||
left paren is indented this many extra spaces, instead of flush with the
|
||||
left paren.
|
||||
c++-friend-offset
|
||||
Offset of C++ friend class declarations relative to member declarations.
|
||||
c++-member-init-indent
|
||||
Indentation level of member initializations in function declarations,
|
||||
if they are on a separate line beginning with a colon.
|
||||
c++-continued-member-init-offset
|
||||
Extra indentation for continuation lines of member initializations; NIL
|
||||
means to align with previous initializations rather than with the colon.
|
||||
|
||||
Settings for K&R, BSD, and Stroustrup indentation styles are
|
||||
c-indent-level 5 8 4
|
||||
c-continued-statement-offset 5 8 4
|
||||
c-continued-brace-offset 0
|
||||
c-brace-offset -5 -8 0
|
||||
c-brace-imaginary-offset 0
|
||||
c-argdecl-indent 0 8 4
|
||||
c-label-offset -5 -8 -4
|
||||
c++-empty-arglist-indent 4
|
||||
c++-friend-offset 0
|
||||
|
||||
Turning on C++ mode calls the value of the variable `c++-mode-hook' with
|
||||
no args if that value is non-nil."
|
||||
(interactive)
|
||||
(kill-all-local-variables)
|
||||
(use-local-map c++-mode-map)
|
||||
(set-syntax-table c++-mode-syntax-table)
|
||||
(setq major-mode 'c++-mode
|
||||
mode-name "C++"
|
||||
comment-column 32
|
||||
local-abbrev-table c++-mode-abbrev-table)
|
||||
(set (make-local-variable 'indent-line-function) 'c++-indent-line)
|
||||
(set (make-local-variable 'comment-start) "// ")
|
||||
(set (make-local-variable 'comment-end) "")
|
||||
(set (make-local-variable 'comment-start-skip) "/\\*+ *\\|// *")
|
||||
(set (make-local-variable 'comment-indent-hook) 'c++-comment-indent)
|
||||
(set (make-local-variable 'paragraph-start) (concat "^$\\|" page-delimiter))
|
||||
(set (make-local-variable 'paragraph-separate) paragraph-start)
|
||||
(set (make-local-variable 'paragraph-ignore-fill-prefix) t)
|
||||
(set (make-local-variable 'require-final-newline) t)
|
||||
(set (make-local-variable 'parse-sexp-ignore-comments) nil)
|
||||
(run-hooks 'c++-mode-hook)
|
||||
(if c++-electric-colon
|
||||
(define-key c++-mode-map ":" 'electric-c++-terminator)))
|
||||
|
||||
;; This is used by indent-for-comment
|
||||
;; to decide how much to indent a comment in C++ code
|
||||
;; based on its context.
|
||||
(defun c++-comment-indent ()
|
||||
(if (looking-at "^\\(/\\*\\|//\\)")
|
||||
0 ; Existing comment at bol stays there.
|
||||
(save-excursion
|
||||
(skip-chars-backward " \t")
|
||||
(max
|
||||
;; leave at least one space on non-empty lines.
|
||||
(if (zerop (current-column)) 0 (1+ (current-column)))
|
||||
(let ((cur-pt (point)))
|
||||
(beginning-of-line 0)
|
||||
;; If previous line had a comment, use it's indent
|
||||
(if (re-search-forward comment-start-skip cur-pt t)
|
||||
(progn
|
||||
(goto-char (match-beginning 0))
|
||||
(current-column))
|
||||
comment-column)))))) ; otherwise indent at comment column.
|
||||
|
||||
(defun electric-c++-brace (arg)
|
||||
"Insert character and correct line's indentation."
|
||||
(interactive "P")
|
||||
(let (insertpos)
|
||||
(if (and (not arg)
|
||||
(eolp)
|
||||
(or (save-excursion
|
||||
(skip-chars-backward " \t")
|
||||
(bolp))
|
||||
(if c-auto-newline (progn (c++-indent-line) (newline) t))))
|
||||
(progn
|
||||
(insert last-command-char)
|
||||
(c++-indent-line)
|
||||
(if c-auto-newline
|
||||
(progn
|
||||
(newline)
|
||||
;; (newline) may have done auto-fill
|
||||
(setq insertpos (- (point) 2))
|
||||
(c++-indent-line)))
|
||||
(save-excursion
|
||||
(if insertpos (goto-char (1+ insertpos)))
|
||||
(delete-char -1))))
|
||||
(if insertpos
|
||||
(save-excursion
|
||||
(goto-char insertpos)
|
||||
(self-insert-command (prefix-numeric-value arg)))
|
||||
(self-insert-command (prefix-numeric-value arg)))))
|
||||
|
||||
(defun electric-c++-semi (arg)
|
||||
"Insert character and correct line's indentation."
|
||||
(interactive "P")
|
||||
(if c-auto-newline
|
||||
(electric-c++-terminator arg)
|
||||
(self-insert-command (prefix-numeric-value arg))))
|
||||
|
||||
(defun electric-c++-terminator (arg)
|
||||
"Insert character and correct line's indentation."
|
||||
(interactive "P")
|
||||
(let (insertpos (end (point)))
|
||||
(if (and (not arg) (eolp)
|
||||
(not (save-excursion
|
||||
(beginning-of-line)
|
||||
(skip-chars-forward " \t")
|
||||
(or (= (following-char) ?#)
|
||||
;; Colon is special only after a label, or
|
||||
;; case, or another colon.
|
||||
;; So quickly rule out most other uses of colon
|
||||
;; and do no indentation for them.
|
||||
(and (eq last-command-char ?:)
|
||||
(not (looking-at "case[ \t]"))
|
||||
(save-excursion
|
||||
(forward-word 1)
|
||||
(skip-chars-forward " \t")
|
||||
(< (point) end))
|
||||
;; Do re-indent double colons
|
||||
(save-excursion
|
||||
(end-of-line 1)
|
||||
(looking-at ":")))
|
||||
(progn
|
||||
(beginning-of-defun)
|
||||
(let ((pps (parse-partial-sexp (point) end)))
|
||||
(or (nth 3 pps) (nth 4 pps) (nth 5 pps))))))))
|
||||
(progn
|
||||
(insert last-command-char)
|
||||
(c++-indent-line)
|
||||
(and c-auto-newline
|
||||
(not (c-inside-parens-p))
|
||||
(progn
|
||||
;; the new marker object, used to be just an integer
|
||||
(setq insertpos (make-marker))
|
||||
;; changed setq to set-marker
|
||||
(set-marker insertpos (1- (point)))
|
||||
;; do this before the newline, since in auto fill can break
|
||||
(newline)
|
||||
(c-indent-line)))
|
||||
(save-excursion
|
||||
(if insertpos (goto-char (1+ insertpos)))
|
||||
(delete-char -1))))
|
||||
(if insertpos
|
||||
(save-excursion
|
||||
(goto-char insertpos)
|
||||
(self-insert-command (prefix-numeric-value arg)))
|
||||
(self-insert-command (prefix-numeric-value arg)))))
|
||||
|
||||
(defun c++-indent-command (&optional whole-exp)
|
||||
"Indent current line as C++ code, or in some cases insert a tab character.
|
||||
If `c-tab-always-indent' is non-nil (the default), always indent current
|
||||
line. Otherwise, indent the current line only if point is at the left
|
||||
margin or in the line's indentation; otherwise insert a tab.
|
||||
|
||||
A numeric argument, regardless of its value, means indent rigidly all means
|
||||
indent rigidly all the lines of the expression starting after point so that
|
||||
this line becomes properly indented. The relative indentation among the
|
||||
lines of the expression are preserved."
|
||||
(interactive "P")
|
||||
(if whole-exp
|
||||
;; If arg, always indent this line as C
|
||||
;; and shift remaining lines of expression the same amount.
|
||||
(let ((shift-amt (c++-indent-line))
|
||||
beg end)
|
||||
(save-excursion
|
||||
(if c-tab-always-indent
|
||||
(beginning-of-line))
|
||||
(setq beg (point))
|
||||
(forward-sexp 1)
|
||||
(setq end (point))
|
||||
(goto-char beg)
|
||||
(forward-line 1)
|
||||
(setq beg (point)))
|
||||
(if (> end beg)
|
||||
(indent-code-rigidly beg end shift-amt "#")))
|
||||
(if (and (not c-tab-always-indent)
|
||||
(save-excursion
|
||||
(skip-chars-backward " \t")
|
||||
(not (bolp))))
|
||||
(insert-tab)
|
||||
(c++-indent-line))))
|
||||
|
||||
(defun c++-indent-line ()
|
||||
"Indent current line as C++ code.
|
||||
Return the amount the indentation changed by."
|
||||
(let ((indent (calculate-c++-indent nil))
|
||||
beg shift-amt
|
||||
(case-fold-search nil)
|
||||
(pos (- (point-max) (point))))
|
||||
(beginning-of-line)
|
||||
(setq beg (point))
|
||||
(cond ((eq indent nil)
|
||||
(setq indent (current-indentation)))
|
||||
((eq indent t)
|
||||
(setq indent (calculate-c-indent-within-comment)))
|
||||
((looking-at "[ \t]*#")
|
||||
(setq indent 0))
|
||||
(t
|
||||
(skip-chars-forward " \t")
|
||||
(if (listp indent) (setq indent (car indent)))
|
||||
(cond ((looking-at "\\(default\\|public\\|private\\|protected\\):")
|
||||
(setq indent (+ indent c-label-offset)))
|
||||
((or (looking-at "case\\b")
|
||||
(and (looking-at "[A-Za-z]")
|
||||
(save-excursion
|
||||
(forward-sexp 1)
|
||||
(looking-at ":[^:]"))))
|
||||
(setq indent (max 1 (+ indent c-label-offset))))
|
||||
((and (looking-at "else\\b")
|
||||
(not (looking-at "else\\s_")))
|
||||
(setq indent (save-excursion
|
||||
(c-backward-to-start-of-if)
|
||||
(current-indentation))))
|
||||
((looking-at "friend\[ \t]class[ \t]")
|
||||
(setq indent (+ indent c++-friend-offset)))
|
||||
((= (following-char) ?})
|
||||
(setq indent (- indent c-indent-level)))
|
||||
((= (following-char) ?{)
|
||||
(setq indent (+ indent c-brace-offset))))))
|
||||
(skip-chars-forward " \t")
|
||||
(setq shift-amt (- indent (current-column)))
|
||||
(if (zerop shift-amt)
|
||||
(if (> (- (point-max) pos) (point))
|
||||
(goto-char (- (point-max) pos)))
|
||||
(delete-region beg (point))
|
||||
(indent-to indent)
|
||||
;; If initial point was within line's indentation,
|
||||
;; position after the indentation. Else stay at same point in text.
|
||||
(if (> (- (point-max) pos) (point))
|
||||
(goto-char (- (point-max) pos))))
|
||||
shift-amt))
|
||||
|
||||
(defun calculate-c++-indent (&optional parse-start)
|
||||
"Return appropriate indentation for current line as C++ code.
|
||||
In usual case returns an integer: the column to indent to.
|
||||
Returns nil if line starts inside a string, t if in a comment."
|
||||
(save-excursion
|
||||
(beginning-of-line)
|
||||
(let ((indent-point (point))
|
||||
(case-fold-search nil)
|
||||
state
|
||||
containing-sexp)
|
||||
(if parse-start
|
||||
(goto-char parse-start)
|
||||
(beginning-of-defun))
|
||||
(while (< (point) indent-point)
|
||||
(setq parse-start (point))
|
||||
(setq state (parse-partial-sexp (point) indent-point 0))
|
||||
(setq containing-sexp (car (cdr state))))
|
||||
(cond ((or (nth 3 state) (nth 4 state))
|
||||
;; return nil or t if should not change this line
|
||||
(nth 4 state))
|
||||
((null containing-sexp)
|
||||
;; Line is at top level. May be data or function definition, or
|
||||
;; may be function argument declaration or member initialization.
|
||||
;; Indent like the previous top level line unless
|
||||
;; (1) the previous line ends in a closeparen without semicolon,
|
||||
;; in which case this line is the first argument declaration or
|
||||
;; member initialization, or
|
||||
;; (2) the previous line begins with a colon,
|
||||
;; in which case this is the second line of member inits.
|
||||
;; It is assumed that arg decls and member inits are not mixed.
|
||||
(goto-char indent-point)
|
||||
(skip-chars-forward " \t")
|
||||
(if (= (following-char) ?{)
|
||||
0 ; Unless it starts a function body
|
||||
(c++-backward-to-noncomment (or parse-start (point-min)))
|
||||
(if (= (preceding-char) ?\))
|
||||
(progn ; first arg decl or member init
|
||||
(goto-char indent-point)
|
||||
(skip-chars-forward " \t")
|
||||
(if (= (following-char) ?:)
|
||||
c++-member-init-indent
|
||||
c-argdecl-indent))
|
||||
(if (= (preceding-char) ?\;)
|
||||
(backward-char 1))
|
||||
(if (= (preceding-char) ?})
|
||||
0
|
||||
(beginning-of-line) ; continued arg decls or member inits
|
||||
(skip-chars-forward " \t")
|
||||
(if (= (following-char) ?:)
|
||||
(if c++-continued-member-init-offset
|
||||
(+ (current-indentation)
|
||||
c++-continued-member-init-offset)
|
||||
(progn
|
||||
(forward-char 1)
|
||||
(skip-chars-forward " \t")
|
||||
(current-column)))
|
||||
(current-indentation)))
|
||||
)))
|
||||
((/= (char-after containing-sexp) ?{)
|
||||
;; line is expression, not statement:
|
||||
;; indent to just after the surrounding open -- unless
|
||||
;; empty arg list, in which case we do what
|
||||
;; c++-empty-arglist-indent says to do.
|
||||
(if (and c++-empty-arglist-indent
|
||||
(or (null (nth 2 state)) ;; indicates empty arg
|
||||
;; list.
|
||||
;; Use a heuristic: if the first
|
||||
;; non-whitespace following left paren on
|
||||
;; same line is not a comment,
|
||||
;; is not an empty arglist.
|
||||
(save-excursion
|
||||
(goto-char (1+ containing-sexp))
|
||||
(not
|
||||
(looking-at "\\( \\|\t\\)*[^/\n]")))))
|
||||
(progn
|
||||
(goto-char containing-sexp)
|
||||
(beginning-of-line)
|
||||
(skip-chars-forward " \t")
|
||||
(goto-char (min (+ (point) c++-empty-arglist-indent)
|
||||
(1+ containing-sexp)))
|
||||
(current-column))
|
||||
;; In C-mode, we would always indent to one after the
|
||||
;; left paren. Here, though, we may have an
|
||||
;; empty-arglist, so we'll indent to the min of that
|
||||
;; and the beginning of the first argument.
|
||||
(goto-char (1+ containing-sexp))
|
||||
(current-column)))
|
||||
(t
|
||||
;; Statement. Find previous non-comment character.
|
||||
(goto-char indent-point)
|
||||
(c++-backward-to-noncomment containing-sexp)
|
||||
(if (not (memq (preceding-char) '(nil ?\, ?\; ?} ?: ?\{)))
|
||||
;; This line is continuation of preceding line's statement;
|
||||
;; indent c-continued-statement-offset more than the
|
||||
;; previous line of the statement.
|
||||
(progn
|
||||
(c-backward-to-start-of-continued-exp containing-sexp)
|
||||
(+ c-continued-statement-offset (current-column)))
|
||||
;; This line starts a new statement.
|
||||
;; Position following last unclosed open.
|
||||
(goto-char containing-sexp)
|
||||
;; Is line first statement after an open-brace?
|
||||
(or
|
||||
;; If no, find that first statement and indent like it.
|
||||
(save-excursion
|
||||
(forward-char 1)
|
||||
(while (progn (skip-chars-forward " \t\n")
|
||||
(looking-at
|
||||
(concat
|
||||
"#\\|/\\*\\|//"
|
||||
"\\|case[ \t]"
|
||||
"\\|[a-zA-Z0-9_$]*:[^:]"
|
||||
"\\|friend[ \t]class[ \t]")))
|
||||
;; Skip over comments and labels following openbrace.
|
||||
(cond ((= (following-char) ?\#)
|
||||
(forward-line 1))
|
||||
((looking-at "/\\*")
|
||||
(search-forward "*/" nil 'move))
|
||||
((looking-at "//\\|friend[ \t]class[ \t]")
|
||||
(forward-line 1))
|
||||
(t
|
||||
(re-search-forward ":[^:]" nil 'move))))
|
||||
;; The first following code counts
|
||||
;; if it is before the line we want to indent.
|
||||
(and (< (point) indent-point)
|
||||
(current-column)))
|
||||
;; If no previous statement,
|
||||
;; indent it relative to line brace is on.
|
||||
;; For open brace in column zero, don't let statement
|
||||
;; start there too. If c-indent-offset is zero,
|
||||
;; use c-brace-offset + c-continued-statement-offset instead.
|
||||
;; For open-braces not the first thing in a line,
|
||||
;; add in c-brace-imaginary-offset.
|
||||
(+ (if (and (bolp) (zerop c-indent-level))
|
||||
(+ c-brace-offset c-continued-statement-offset)
|
||||
c-indent-level)
|
||||
;; Move back over whitespace before the openbrace.
|
||||
;; If openbrace is not first nonwhite thing on the line,
|
||||
;; add the c-brace-imaginary-offset.
|
||||
(progn (skip-chars-backward " \t")
|
||||
(if (bolp) 0 c-brace-imaginary-offset))
|
||||
;; If the openbrace is preceded by a parenthesized exp,
|
||||
;; move to the beginning of that;
|
||||
;; possibly a different line
|
||||
(progn
|
||||
(if (eq (preceding-char) ?\))
|
||||
(forward-sexp -1))
|
||||
;; Get initial indentation of the line we are on.
|
||||
(current-indentation))))))))))
|
||||
|
||||
(defun c++-backward-to-noncomment (lim)
|
||||
(let (opoint stop)
|
||||
(while (not stop)
|
||||
(skip-chars-backward " \t\n\r\f" lim)
|
||||
(setq opoint (point))
|
||||
(cond ((and (>= (point) (+ 2 lim))
|
||||
(save-excursion
|
||||
(forward-char -2)
|
||||
(looking-at "\\*/")))
|
||||
(search-backward "/*" lim 'move))
|
||||
((and
|
||||
(search-backward "//" (max (point-bol) lim) 'move)
|
||||
(not (within-string-p (point) opoint))))
|
||||
(t (beginning-of-line)
|
||||
(skip-chars-forward " \t")
|
||||
(if (looking-at "#")
|
||||
(setq stop (<= (point) lim))
|
||||
(setq stop t)
|
||||
(goto-char opoint)))))))
|
||||
|
||||
(defun indent-c++-exp ()
|
||||
"Indent each line of the C++ grouping following point."
|
||||
(interactive)
|
||||
(let ((indent-stack (list nil))
|
||||
(contain-stack (list (point)))
|
||||
(case-fold-search nil)
|
||||
restart outer-loop-done inner-loop-done state ostate
|
||||
this-indent last-sexp
|
||||
at-else at-brace
|
||||
(opoint (point))
|
||||
(next-depth 0))
|
||||
(save-excursion
|
||||
(forward-sexp 1))
|
||||
(save-excursion
|
||||
(setq outer-loop-done nil)
|
||||
(while (and (not (eobp)) (not outer-loop-done))
|
||||
(setq last-depth next-depth)
|
||||
;; Compute how depth changes over this line
|
||||
;; plus enough other lines to get to one that
|
||||
;; does not end inside a comment or string.
|
||||
;; Meanwhile, do appropriate indentation on comment lines.
|
||||
(setq innerloop-done nil)
|
||||
(while (and (not innerloop-done)
|
||||
(not (and (eobp) (setq outer-loop-done t))))
|
||||
(setq ostate state)
|
||||
(setq state (parse-partial-sexp (point) (progn (end-of-line) (point))
|
||||
nil nil state))
|
||||
(setq next-depth (car state))
|
||||
(if (and (car (cdr (cdr state)))
|
||||
(>= (car (cdr (cdr state))) 0))
|
||||
(setq last-sexp (car (cdr (cdr state)))))
|
||||
(if (or (nth 4 ostate))
|
||||
(c++-indent-line))
|
||||
(if (or (nth 3 state))
|
||||
(forward-line 1)
|
||||
(setq innerloop-done t)))
|
||||
(if (<= next-depth 0)
|
||||
(setq outer-loop-done t))
|
||||
(if outer-loop-done
|
||||
nil
|
||||
;; If this line had ..))) (((.. in it, pop out of the levels
|
||||
;; that ended anywhere in this line, even if the final depth
|
||||
;; doesn't indicate that they ended.
|
||||
(while (> last-depth (nth 6 state))
|
||||
(setq indent-stack (cdr indent-stack)
|
||||
contain-stack (cdr contain-stack)
|
||||
last-depth (1- last-depth)))
|
||||
(if (/= last-depth next-depth)
|
||||
(setq last-sexp nil))
|
||||
;; Add levels for any parens that were started in this line.
|
||||
(while (< last-depth next-depth)
|
||||
(setq indent-stack (cons nil indent-stack)
|
||||
contain-stack (cons nil contain-stack)
|
||||
last-depth (1+ last-depth)))
|
||||
(if (null (car contain-stack))
|
||||
(setcar contain-stack (or (car (cdr state))
|
||||
(save-excursion (forward-sexp -1)
|
||||
(point)))))
|
||||
(forward-line 1)
|
||||
(skip-chars-forward " \t")
|
||||
(if (eolp)
|
||||
nil
|
||||
(if (and (car indent-stack)
|
||||
(>= (car indent-stack) 0))
|
||||
;; Line is on an existing nesting level.
|
||||
;; Lines inside parens are handled specially.
|
||||
(if (/= (char-after (car contain-stack)) ?{)
|
||||
(setq this-indent (car indent-stack))
|
||||
;; Line is at statement level.
|
||||
;; Is it a new statement? Is it an else?
|
||||
;; Find last non-comment character before this line
|
||||
(save-excursion
|
||||
(setq at-else (looking-at "else\\W"))
|
||||
(setq at-brace (= (following-char) ?{))
|
||||
(c++-backward-to-noncomment opoint)
|
||||
(if (not (memq (preceding-char) '(nil ?\, ?\; ?} ?: ?{)))
|
||||
;; Preceding line did not end in comma or semi;
|
||||
;; indent this line c-continued-statement-offset
|
||||
;; more than previous.
|
||||
(progn
|
||||
(c-backward-to-start-of-continued-exp
|
||||
(car contain-stack))
|
||||
(setq this-indent
|
||||
(+ c-continued-statement-offset
|
||||
(current-column)
|
||||
(if at-brace c-continued-brace-offset 0))))
|
||||
;; Preceding line ended in comma or semi;
|
||||
;; use the standard indent for this level.
|
||||
(if at-else
|
||||
(progn (c-backward-to-start-of-if opoint)
|
||||
(setq this-indent (current-indentation)))
|
||||
(setq this-indent (car indent-stack))))))
|
||||
;; Just started a new nesting level.
|
||||
;; Compute the standard indent for this level.
|
||||
(let ((val (calculate-c++-indent
|
||||
(if (car indent-stack)
|
||||
(- (car indent-stack))))))
|
||||
(setcar indent-stack
|
||||
(setq this-indent val))))
|
||||
;; Adjust line indentation according to its contents
|
||||
(if (looking-at "\\(public\\|private\\|protected\\):")
|
||||
(setq this-indent (- this-indent c-indent-level)))
|
||||
(if (or (looking-at "case[ \t]")
|
||||
(and (looking-at "[A-Za-z]")
|
||||
(save-excursion
|
||||
(forward-sexp 1)
|
||||
(looking-at ":[^:]"))))
|
||||
(setq this-indent (max 1 (+ this-indent c-label-offset))))
|
||||
(if (looking-at "friend[ \t]class[ \t]")
|
||||
(setq this-indent (+ this-indent c++-friend-offset)))
|
||||
(if (= (following-char) ?})
|
||||
(setq this-indent (- this-indent c-indent-level)))
|
||||
(if (= (following-char) ?{)
|
||||
(setq this-indent (+ this-indent c-brace-offset)))
|
||||
;; Put chosen indentation into effect.
|
||||
(or (= (current-column) this-indent)
|
||||
(= (following-char) ?\#)
|
||||
(progn
|
||||
(delete-region (point) (progn (beginning-of-line) (point)))
|
||||
(indent-to this-indent)))
|
||||
;; Indent any comment following the text.
|
||||
(or (looking-at comment-start-skip)
|
||||
(if (re-search-forward comment-start-skip
|
||||
(save-excursion (end-of-line)
|
||||
(point)) t)
|
||||
(progn
|
||||
(indent-for-comment)
|
||||
(beginning-of-line))))))))))
|
||||
|
||||
(defun fill-C-comment ()
|
||||
(interactive)
|
||||
(save-excursion
|
||||
(let ((save fill-prefix))
|
||||
(beginning-of-line 1)
|
||||
(save-excursion
|
||||
(re-search-forward comment-start-skip
|
||||
(save-excursion (end-of-line) (point))
|
||||
t)
|
||||
(goto-char (match-end 0))
|
||||
(set-fill-prefix))
|
||||
(while (looking-at fill-prefix)
|
||||
(previous-line 1))
|
||||
(next-line 1)
|
||||
(insert-string "\n")
|
||||
(fill-paragraph nil)
|
||||
(delete-char -1)
|
||||
(setq fill-prefix save))))
|
||||
|
||||
(defun point-bol ()
|
||||
"Returns the value of the point at the beginning of the current line."
|
||||
(save-excursion
|
||||
(beginning-of-line)
|
||||
(point)))
|
||||
|
||||
(defun c++-insert-header ()
|
||||
"Insert header denoting C++ code at top of buffer."
|
||||
(interactive)
|
||||
(save-excursion
|
||||
(goto-char (point-min))
|
||||
(insert "// "
|
||||
"This may look like C code, but it is really "
|
||||
"-*- C++ -*-"
|
||||
"\n\n")))
|
||||
|
||||
(defun within-string-p (point1 point2)
|
||||
"Returns true if number of double quotes between two points is odd."
|
||||
(let ((s (buffer-substring point1 point2)))
|
||||
(not (zerop (mod (count-char-in-string ?\" s) 2)))))
|
||||
|
||||
(defun count-char-in-string (c s)
|
||||
(let ((count 0)
|
||||
(pos 0))
|
||||
(while (< pos (length s))
|
||||
(setq count (+ count (if (\= (aref s pos) c) 1 0)))
|
||||
(setq pos (1+ pos)))
|
||||
count))
|
||||
|
||||
;;; This page covers "macroization;" making C++ parameterized types
|
||||
;;; via macros.
|
||||
|
||||
(defvar c++-default-macroize-column 78
|
||||
"Place to insert backslashes.")
|
||||
|
||||
(defun c++-macroize-region (from to arg)
|
||||
"Insert backslashes at end of every line in region. Useful for defining cpp
|
||||
macros. If called with negative argument, will remove trailing backslashes,
|
||||
so that indentation will work right."
|
||||
(interactive "r\np")
|
||||
(save-excursion
|
||||
(goto-char from)
|
||||
(beginning-of-line 1)
|
||||
(let ((line (count-lines (point-min) (point)))
|
||||
(to-line (save-excursion (goto-char to)
|
||||
(count-lines (point-min) (point)))))
|
||||
(while (< line to-line)
|
||||
(backslashify-current-line (> arg 0))
|
||||
(next-line 1) (setq line (1+ line))))))
|
||||
|
||||
(defun backslashify-current-line (doit)
|
||||
(end-of-line 1)
|
||||
(cond
|
||||
(doit
|
||||
;; Note that "\\\\" is needed to get one backslash.
|
||||
(if (not (save-excursion (forward-char -1) (looking-at "\\\\")))
|
||||
(progn
|
||||
(if (>= (current-column) c++-default-macroize-column)
|
||||
(insert " \\")
|
||||
(while (<= (current-column) c++-default-macroize-column)
|
||||
(insert "\t") (end-of-line))
|
||||
(delete-char -1)
|
||||
(while (< (current-column) c++-default-macroize-column)
|
||||
(insert " ") (end-of-line))
|
||||
(insert "\\")))))
|
||||
(t
|
||||
(forward-char -1)
|
||||
(if (looking-at "\\\\")
|
||||
(progn (skip-chars-backward " \t")
|
||||
(kill-line))))))
|
||||
|
||||
|
||||
;;; This page covers commenting out multiple lines.
|
||||
|
||||
(defun c++-comment-region ()
|
||||
"Comment out all lines in a region between mark and current point.
|
||||
Inserts \"// \" (`comment-start') in front of each line."
|
||||
(interactive)
|
||||
(let* ((m (if (eq (mark) nil) (error "Mark is not set!") (mark)))
|
||||
(start (if (< (point) m) (point) m))
|
||||
(end (if (> (point) m) (point) m))
|
||||
(mymark (copy-marker end)))
|
||||
(save-excursion
|
||||
(goto-char start)
|
||||
(while (< (point) (marker-position mymark))
|
||||
(beginning-of-line)
|
||||
(insert comment-start)
|
||||
(beginning-of-line)
|
||||
(next-line 1)))))
|
||||
|
||||
(defun c++-uncomment-region ()
|
||||
"Uncomment all lines in region between mark and current point.
|
||||
Deletes the leading \"// \" (`comment-start') from each line, if any."
|
||||
(interactive)
|
||||
(let* ((m (if (eq (mark) nil) (error "Mark is not set!") (mark)))
|
||||
(start (if (< (point) m) (point) m))
|
||||
(end (if (> (point) m) (point) m))
|
||||
(mymark (copy-marker end))
|
||||
(len (length comment-start))
|
||||
(char (string-to-char comment-start)))
|
||||
(save-excursion
|
||||
(goto-char start)
|
||||
(while (< (point) (marker-position mymark))
|
||||
(beginning-of-line)
|
||||
(if (looking-at (concat " *" comment-start))
|
||||
(progn
|
||||
(zap-to-char 1 char)
|
||||
(delete-char len)))
|
||||
(beginning-of-line)
|
||||
(next-line 1)))))
|
||||
|
||||
;;; Below are two regular expressions that attempt to match defuns
|
||||
;;; "strongly" and "weakly." The strong one almost reconstructs the
|
||||
;;; grammar of C++; the weak one just figures anything id or curly on
|
||||
;;; the left begins a defun. The constant "c++-match-header-strongly"
|
||||
;;; determines which to use; the default is the weak one.
|
||||
|
||||
(defvar c++-match-header-strongly nil
|
||||
"*If nil, use `c++-defun-header-weak' to identify beginning of definitions.
|
||||
If non-nil, use `c++-defun-header-strong'.")
|
||||
|
||||
(defvar c++-defun-header-strong-struct-equivs "\\(class\\|struct\\|enum\\)"
|
||||
"Regexp to match names of structure declaration blocks in C++.")
|
||||
|
||||
(defconst c++-defun-header-strong
|
||||
(let*
|
||||
(; valid identifiers
|
||||
;; There's a real wierdness here -- if I switch the below
|
||||
(id "\\(\\w\\|_\\)+")
|
||||
;; to be
|
||||
;; (id "\\(_\\|\\w\\)+")
|
||||
;; things no longer work right. Try it and see!
|
||||
|
||||
; overloadable operators
|
||||
(op-sym1
|
||||
"[---+*/%^&|~!=<>]\\|[---+*/%^&|<>=!]=\\|<<=?\\|>>=?")
|
||||
(op-sym2
|
||||
"&&\\|||\\|\\+\\+\\|--\\|()\\|\\[\\]")
|
||||
(op-sym (concat "\\(" op-sym1 "\\|" op-sym2 "\\)"))
|
||||
; whitespace
|
||||
(middle "[^\\*]*\\(\\*+[^/\\*][^\\*]*\\)*")
|
||||
(c-comment (concat "/\\*" middle "\\*+/"))
|
||||
(wh (concat "\\(\\s \\|\n\\|//.*$\\|" c-comment "\\)"))
|
||||
(wh-opt (concat wh "*"))
|
||||
(wh-nec (concat wh "+"))
|
||||
(oper (concat "\\(" "operator" "\\("
|
||||
wh-opt op-sym "\\|" wh-nec id "\\)" "\\)"))
|
||||
(dcl-list "([^():]*)")
|
||||
(func-name (concat "\\(" oper "\\|" id "::" id "\\|" id "\\)"))
|
||||
(inits
|
||||
(concat "\\(:"
|
||||
"\\(" wh-opt id "(.*\\()" wh-opt "," "\\)\\)*"
|
||||
wh-opt id "(.*)" wh-opt "{"
|
||||
"\\|" wh-opt "{\\)"))
|
||||
(type-name (concat
|
||||
"\\(" c++-defun-header-strong-struct-equivs wh-nec "\\)?"
|
||||
id))
|
||||
(type (concat "\\(const" wh-nec "\\)?"
|
||||
"\\(" type-name "\\|" type-name wh-opt "\\*+" "\\|"
|
||||
type-name wh-opt "&" "\\)"))
|
||||
(modifier "\\(inline\\|virtual\\|overload\\|auto\\|static\\)")
|
||||
(modifiers (concat "\\(" modifier wh-nec "\\)*"))
|
||||
(func-header
|
||||
;; type arg-dcl
|
||||
(concat modifiers type wh-nec func-name wh-opt dcl-list wh-opt inits))
|
||||
(inherit (concat "\\(:" wh-opt "\\(public\\|private\\)?"
|
||||
wh-nec id "\\)"))
|
||||
(cs-header (concat
|
||||
c++-defun-header-strong-struct-equivs
|
||||
wh-nec id wh-opt inherit "?" wh-opt "{")))
|
||||
(concat "^\\(" func-header "\\|" cs-header "\\)"))
|
||||
"Strongly-defined regexp to match beginning of structure or function def.")
|
||||
|
||||
|
||||
;; This part has to do with recognizing defuns.
|
||||
|
||||
;; The weak convention we will use is that a defun begins any time
|
||||
;; there is a left curly brace, or some identifier on the left margin,
|
||||
;; followed by a left curly somewhere on the line. (This will also
|
||||
;; incorrectly match some continued strings, but this is after all
|
||||
;; just a weak heuristic.) Suggestions for improvement (short of the
|
||||
;; strong scheme shown above) are welcomed.
|
||||
|
||||
(defconst c++-defun-header-weak "^{\\|^[_a-zA-Z].*{"
|
||||
"Weakly-defined regexp to match beginning of structure or function def.")
|
||||
|
||||
(defun c++-beginning-of-defun (arg)
|
||||
(interactive "p")
|
||||
(let ((c++-defun-header (if c++-match-header-strongly
|
||||
c++-defun-header-strong
|
||||
c++-defun-header-weak)))
|
||||
(cond ((or (= arg 0) (and (> arg 0) (bobp))) nil)
|
||||
((and (not (looking-at c++-defun-header))
|
||||
(let ((curr-pos (point))
|
||||
(open-pos (if (search-forward "{" nil 'move)
|
||||
(point)))
|
||||
(beg-pos
|
||||
(if (re-search-backward c++-defun-header nil 'move)
|
||||
(match-beginning 0))))
|
||||
(if (and open-pos beg-pos
|
||||
(< beg-pos curr-pos)
|
||||
(> open-pos curr-pos))
|
||||
(progn
|
||||
(goto-char beg-pos)
|
||||
(if (= arg 1) t nil));; Are we done?
|
||||
(goto-char curr-pos)
|
||||
nil))))
|
||||
(t
|
||||
(if (and (looking-at c++-defun-header) (not (bobp)))
|
||||
(forward-char (if (< arg 0) 1 -1)))
|
||||
(and (re-search-backward c++-defun-header nil 'move (or arg 1))
|
||||
(goto-char (match-beginning 0)))))))
|
||||
|
||||
|
||||
(defun c++-end-of-defun (arg)
|
||||
(interactive "p")
|
||||
(let ((c++-defun-header (if c++-match-header-strongly
|
||||
c++-defun-header-strong
|
||||
c++-defun-header-weak)))
|
||||
(if (and (eobp) (> arg 0))
|
||||
nil
|
||||
(if (and (> arg 0) (looking-at c++-defun-header)) (forward-char 1))
|
||||
(let ((pos (point)))
|
||||
(c++-beginning-of-defun
|
||||
(if (< arg 0)
|
||||
(- (- arg (if (eobp) 0 1)))
|
||||
arg))
|
||||
(if (and (< arg 0) (bobp))
|
||||
t
|
||||
(if (re-search-forward c++-defun-header nil 'move)
|
||||
(progn (forward-char -1)
|
||||
(forward-sexp)
|
||||
(beginning-of-line 2)))
|
||||
(if (and (= pos (point))
|
||||
(re-search-forward c++-defun-header nil 'move))
|
||||
(c++-end-of-defun 1))))
|
||||
t)))
|
||||
|
||||
(defun c++-indent-defun ()
|
||||
"Indents the current function definition, struct or class declaration."
|
||||
(interactive)
|
||||
(let ((restore (point)))
|
||||
(c++-end-of-defun 1)
|
||||
(beginning-of-line 1)
|
||||
(let ((end (point)))
|
||||
(c++-beginning-of-defun 1)
|
||||
(while (<= (point) end)
|
||||
(c++-indent-line)
|
||||
(next-line 1)
|
||||
(beginning-of-line 1)))
|
||||
(goto-char restore)))
|
1020
lisp/textmodes/bibtex.el
Normal file
1020
lisp/textmodes/bibtex.el
Normal file
File diff suppressed because it is too large
Load Diff
Loading…
x
Reference in New Issue
Block a user