(require 'cl-lib)
(require 'macroexp)
+;; `gv' is required here because cl-macs can be loaded before loaddefs.el.
+(require 'gv)
(defmacro cl-pop2 (place)
(declare (debug edebug-sexps))
\(fn NAME ARGLIST [DOCSTRING] BODY...)"
(declare (debug
;; Same as defun but use cl-lambda-list.
- (&define [&or name ("cl-setf" :name cl-setf name)]
+ (&define [&or name ("setf" :name setf name)]
cl-lambda-list
cl-declarations-or-string
[&optional ("interactive" interactive)]
(when (cdr (assq (symbol-name cl-macro) cl-env))
(setq cl-macro (cadr (assq (symbol-name cl-macro) cl-env)))))
((eq 'setq (car-safe cl-macro))
- ;; Convert setq to cl-setf if required by symbol-macro expansion.
+ ;; Convert setq to setf if required by symbol-macro expansion.
(let* ((args (mapcar (lambda (f) (cl--sm-macroexpand f cl-env))
(cdr cl-macro)))
(p args))
(while (and p (symbolp (car p))) (setq p (cddr p)))
- (if p (setq cl-macro (cons 'cl-setf args))
+ (if p (setq cl-macro (cons 'setf args))
(setq cl-macro (cons 'setq args))
;; Don't loop further.
nil))))))
(defmacro cl-symbol-macrolet (bindings &rest body)
"Make symbol macro definitions.
Within the body FORMs, references to the variable NAME will be replaced
-by EXPANSION, and (setq NAME ...) will act like (cl-setf EXPANSION ...).
+by EXPANSION, and (setq NAME ...) will act like (setf EXPANSION ...).
\(fn ((NAME EXPANSION) ...) FORM...)"
(declare (indent 1) (debug ((&rest (symbol sexp)) cl-declarations body)))
;;; Generalized variables.
-;;;###autoload
-(defmacro cl-define-setf-expander (func args &rest body)
- "Define a `cl-setf' method.
-This method shows how to handle `cl-setf's to places of the form (NAME ARGS...).
-The argument forms ARGS are bound according to ARGLIST, as if NAME were
-going to be expanded as a macro, then the BODY forms are executed and must
-return a list of five elements: a temporary-variables list, a value-forms
-list, a store-variables list (of length one), a store-form, and an access-
-form. See `cl-defsetf' for a simpler way to define most setf-methods.
-
-\(fn NAME ARGLIST BODY...)"
- (declare (debug
- (&define name cl-lambda-list cl-declarations-or-string def-body)))
- `(cl-eval-when (compile load eval)
- ,@(if (stringp (car body))
- (list `(put ',func 'setf-documentation ,(pop body))))
- (put ',func 'setf-method (cl-function (lambda ,args ,@body)))))
-
-;;;###autoload
-(defmacro cl-defsetf (func arg1 &rest args)
- "Define a `cl-setf' method.
-This macro is an easy-to-use substitute for `cl-define-setf-expander' that works
-well for simple place forms. In the simple `cl-defsetf' form, `cl-setf's of
-the form (cl-setf (NAME ARGS...) VAL) are transformed to function or macro
-calls of the form (FUNC ARGS... VAL). Example:
-
- (cl-defsetf aref aset)
-
-Alternate form: (cl-defsetf NAME ARGLIST (STORE) BODY...).
-Here, the above `cl-setf' call is expanded by binding the argument forms ARGS
-according to ARGLIST, binding the value form VAL to STORE, then executing
-BODY, which must return a Lisp form that does the necessary `cl-setf' operation.
-Actually, ARGLIST and STORE may be bound to temporary variables which are
-introduced automatically to preserve proper execution order of the arguments.
-Example:
-
- (cl-defsetf nth (n x) (v) `(setcar (nthcdr ,n ,x) ,v))
-
-\(fn NAME [FUNC | ARGLIST (STORE) BODY...])"
- (declare (debug
- (&define name
- [&or [symbolp &optional stringp]
- [cl-lambda-list (symbolp)]]
- cl-declarations-or-string def-body)))
- (if (and (listp arg1) (consp args))
- (let* ((largs nil) (largsr nil)
- (temps nil) (tempsr nil)
- (restarg nil) (rest-temps nil)
- (store-var (car (prog1 (car args) (setq args (cdr args)))))
- (store-temp (intern (format "--%s--temp--" store-var)))
- (lets1 nil) (lets2 nil)
- (docstr nil) (p arg1))
- (if (stringp (car args))
- (setq docstr (prog1 (car args) (setq args (cdr args)))))
- (while (and p (not (eq (car p) '&aux)))
- (if (eq (car p) '&rest)
- (setq p (cdr p) restarg (car p))
- (or (memq (car p) '(&optional &key &allow-other-keys))
- (setq largs (cons (if (consp (car p)) (car (car p)) (car p))
- largs)
- temps (cons (intern (format "--%s--temp--" (car largs)))
- temps))))
- (setq p (cdr p)))
- (setq largs (nreverse largs) temps (nreverse temps))
- (if restarg
- (setq largsr (append largs (list restarg))
- rest-temps (intern (format "--%s--temp--" restarg))
- tempsr (append temps (list rest-temps)))
- (setq largsr largs tempsr temps))
- (let ((p1 largs) (p2 temps))
- (while p1
- (setq lets1 (cons `(,(car p2)
- (make-symbol ,(format "--cl-%s--" (car p1))))
- lets1)
- lets2 (cons (list (car p1) (car p2)) lets2)
- p1 (cdr p1) p2 (cdr p2))))
- (if restarg (setq lets2 (cons (list restarg rest-temps) lets2)))
- `(cl-define-setf-expander ,func ,arg1
- ,@(and docstr (list docstr))
- (let*
- ,(nreverse
- (cons `(,store-temp
- (make-symbol ,(format "--cl-%s--" store-var)))
- (if restarg
- `((,rest-temps
- (mapcar (lambda (_) (make-symbol "--cl-var--"))
- ,restarg))
- ,@lets1)
- lets1)))
- (list ; 'values
- (,(if restarg 'cl-list* 'list) ,@tempsr)
- (,(if restarg 'cl-list* 'list) ,@largsr)
- (list ,store-temp)
- (let*
- ,(nreverse
- (cons (list store-var store-temp)
- lets2))
- ,@args)
- (,(if restarg 'cl-list* 'list)
- ,@(cons `',func tempsr))))))
- `(cl-defsetf ,func (&rest args) (store)
- ,(let ((call `(cons ',arg1
- (append args (list store)))))
- (if (car args)
- `(list 'progn ,call store)
- call)))))
-
;;; Some standard place types from Common Lisp.
-(cl-defsetf aref aset)
-(cl-defsetf car setcar)
-(cl-defsetf cdr setcdr)
-(cl-defsetf caar (x) (val) `(setcar (car ,x) ,val))
-(cl-defsetf cadr (x) (val) `(setcar (cdr ,x) ,val))
-(cl-defsetf cdar (x) (val) `(setcdr (car ,x) ,val))
-(cl-defsetf cddr (x) (val) `(setcdr (cdr ,x) ,val))
-(cl-defsetf elt (seq n) (store)
- `(if (listp ,seq) (setcar (nthcdr ,n ,seq) ,store)
- (aset ,seq ,n ,store)))
-(cl-defsetf get put)
-(cl-defsetf cl-get (x y &optional d) (store) `(put ,x ,y ,store))
-(cl-defsetf gethash (x h &optional d) (store) `(puthash ,x ,store ,h))
-(cl-defsetf nth (n x) (store) `(setcar (nthcdr ,n ,x) ,store))
-(cl-defsetf cl-subseq (seq start &optional end) (new)
+(gv-define-setter cl-get (store x y &optional d) `(put ,x ,y ,store))
+(gv-define-setter cl-subseq (new seq start &optional end)
`(progn (cl-replace ,seq ,new :start1 ,start :end1 ,end) ,new))
-(cl-defsetf symbol-function fset)
-(cl-defsetf symbol-plist setplist)
-(cl-defsetf symbol-value set)
;;; Various car/cdr aliases. Note that `cadr' is handled specially.
-(cl-defsetf cl-first setcar)
-(cl-defsetf cl-second (x) (store) `(setcar (cdr ,x) ,store))
-(cl-defsetf cl-third (x) (store) `(setcar (cddr ,x) ,store))
-(cl-defsetf cl-fourth (x) (store) `(setcar (cl-cdddr ,x) ,store))
-(cl-defsetf cl-fifth (x) (store) `(setcar (nthcdr 4 ,x) ,store))
-(cl-defsetf cl-sixth (x) (store) `(setcar (nthcdr 5 ,x) ,store))
-(cl-defsetf cl-seventh (x) (store) `(setcar (nthcdr 6 ,x) ,store))
-(cl-defsetf cl-eighth (x) (store) `(setcar (nthcdr 7 ,x) ,store))
-(cl-defsetf cl-ninth (x) (store) `(setcar (nthcdr 8 ,x) ,store))
-(cl-defsetf cl-tenth (x) (store) `(setcar (nthcdr 9 ,x) ,store))
-(cl-defsetf cl-rest setcdr)
+(gv-define-setter cl-fourth (store x) `(setcar (cl-cdddr ,x) ,store))
+(gv-define-setter cl-fifth (store x) `(setcar (nthcdr 4 ,x) ,store))
+(gv-define-setter cl-sixth (store x) `(setcar (nthcdr 5 ,x) ,store))
+(gv-define-setter cl-seventh (store x) `(setcar (nthcdr 6 ,x) ,store))
+(gv-define-setter cl-eighth (store x) `(setcar (nthcdr 7 ,x) ,store))
+(gv-define-setter cl-ninth (store x) `(setcar (nthcdr 8 ,x) ,store))
+(gv-define-setter cl-tenth (store x) `(setcar (nthcdr 9 ,x) ,store))
;;; Some more Emacs-related place types.
-(cl-defsetf buffer-file-name set-visited-file-name t)
-(cl-defsetf buffer-modified-p (&optional buf) (flag)
+(gv-define-simple-setter buffer-file-name set-visited-file-name t)
+(gv-define-setter buffer-modified-p (flag &optional buf)
`(with-current-buffer ,buf
(set-buffer-modified-p ,flag)))
-(cl-defsetf buffer-name rename-buffer t)
-(cl-defsetf buffer-string () (store)
+(gv-define-simple-setter buffer-name rename-buffer t)
+(gv-define-setter buffer-string (store)
`(progn (erase-buffer) (insert ,store)))
-(cl-defsetf buffer-substring cl--set-buffer-substring)
-(cl-defsetf current-buffer set-buffer)
-(cl-defsetf current-case-table set-case-table)
-(cl-defsetf current-column move-to-column t)
-(cl-defsetf current-global-map use-global-map t)
-(cl-defsetf current-input-mode () (store)
+(gv-define-simple-setter buffer-substring cl--set-buffer-substring)
+(gv-define-simple-setter current-buffer set-buffer)
+(gv-define-simple-setter current-case-table set-case-table)
+(gv-define-simple-setter current-column move-to-column t)
+(gv-define-simple-setter current-global-map use-global-map t)
+(gv-define-setter current-input-mode (store)
`(progn (apply #'set-input-mode ,store) ,store))
-(cl-defsetf current-local-map use-local-map t)
-(cl-defsetf current-window-configuration set-window-configuration t)
-(cl-defsetf default-file-modes set-default-file-modes t)
-(cl-defsetf default-value set-default)
-(cl-defsetf documentation-property put)
-(cl-defsetf face-background (f &optional s) (x) `(set-face-background ,f ,x ,s))
-(cl-defsetf face-background-pixmap (f &optional s) (x)
+(gv-define-simple-setter current-local-map use-local-map t)
+(gv-define-simple-setter current-window-configuration set-window-configuration t)
+(gv-define-simple-setter default-file-modes set-default-file-modes t)
+(gv-define-simple-setter documentation-property put)
+(gv-define-setter face-background (x f &optional s) `(set-face-background ,f ,x ,s))
+(gv-define-setter face-background-pixmap (x f &optional s)
`(set-face-background-pixmap ,f ,x ,s))
-(cl-defsetf face-font (f &optional s) (x) `(set-face-font ,f ,x ,s))
-(cl-defsetf face-foreground (f &optional s) (x) `(set-face-foreground ,f ,x ,s))
-(cl-defsetf face-underline-p (f &optional s) (x)
+(gv-define-setter face-font (x f &optional s) `(set-face-font ,f ,x ,s))
+(gv-define-setter face-foreground (x f &optional s) `(set-face-foreground ,f ,x ,s))
+(gv-define-setter face-underline-p (x f &optional s)
`(set-face-underline-p ,f ,x ,s))
-(cl-defsetf file-modes set-file-modes t)
-(cl-defsetf frame-height set-screen-height t)
-(cl-defsetf frame-parameters modify-frame-parameters t)
-(cl-defsetf frame-visible-p cl--set-frame-visible-p)
-(cl-defsetf frame-width set-screen-width t)
-(cl-defsetf frame-parameter set-frame-parameter t)
-(cl-defsetf terminal-parameter set-terminal-parameter)
-(cl-defsetf getenv setenv t)
-(cl-defsetf get-register set-register)
-(cl-defsetf global-key-binding global-set-key)
-(cl-defsetf keymap-parent set-keymap-parent)
-(cl-defsetf local-key-binding local-set-key)
-(cl-defsetf mark set-mark t)
-(cl-defsetf mark-marker set-mark t)
-(cl-defsetf marker-position set-marker t)
-(cl-defsetf match-data set-match-data t)
-(cl-defsetf mouse-position (scr) (store)
+(gv-define-simple-setter file-modes set-file-modes t)
+(gv-define-simple-setter frame-height set-screen-height t)
+(gv-define-simple-setter frame-parameters modify-frame-parameters t)
+(gv-define-simple-setter frame-visible-p cl--set-frame-visible-p)
+(gv-define-simple-setter frame-width set-screen-width t)
+(gv-define-simple-setter getenv setenv t)
+(gv-define-simple-setter get-register set-register)
+(gv-define-simple-setter global-key-binding global-set-key)
+(gv-define-simple-setter local-key-binding local-set-key)
+(gv-define-simple-setter mark set-mark t)
+(gv-define-simple-setter mark-marker set-mark t)
+(gv-define-simple-setter marker-position set-marker t)
+(gv-define-setter mouse-position (store scr)
`(set-mouse-position ,scr (car ,store) (cadr ,store)
(cddr ,store)))
-(cl-defsetf overlay-get overlay-put)
-(cl-defsetf overlay-start (ov) (store)
- `(progn (move-overlay ,ov ,store (overlay-end ,ov)) ,store))
-(cl-defsetf overlay-end (ov) (store)
- `(progn (move-overlay ,ov (overlay-start ,ov) ,store) ,store))
-(cl-defsetf point goto-char)
-(cl-defsetf point-marker goto-char t)
-(cl-defsetf point-max () (store)
+(gv-define-simple-setter point goto-char)
+(gv-define-simple-setter point-marker goto-char t)
+(gv-define-setter point-max (store)
`(progn (narrow-to-region (point-min) ,store) ,store))
-(cl-defsetf point-min () (store)
+(gv-define-setter point-min (store)
`(progn (narrow-to-region ,store (point-max)) ,store))
-(cl-defsetf process-buffer set-process-buffer)
-(cl-defsetf process-filter set-process-filter)
-(cl-defsetf process-sentinel set-process-sentinel)
-(cl-defsetf process-get process-put)
-(cl-defsetf read-mouse-position (scr) (store)
+(gv-define-setter read-mouse-position (store scr)
`(set-mouse-position ,scr (car ,store) (cdr ,store)))
-(cl-defsetf screen-height set-screen-height t)
-(cl-defsetf screen-width set-screen-width t)
-(cl-defsetf selected-window select-window)
-(cl-defsetf selected-screen select-screen)
-(cl-defsetf selected-frame select-frame)
-(cl-defsetf standard-case-table set-standard-case-table)
-(cl-defsetf syntax-table set-syntax-table)
-(cl-defsetf visited-file-modtime set-visited-file-modtime t)
-(cl-defsetf window-buffer set-window-buffer t)
-(cl-defsetf window-display-table set-window-display-table t)
-(cl-defsetf window-dedicated-p set-window-dedicated-p t)
-(cl-defsetf window-height () (store)
+(gv-define-simple-setter screen-height set-screen-height t)
+(gv-define-simple-setter screen-width set-screen-width t)
+(gv-define-simple-setter selected-window select-window)
+(gv-define-simple-setter selected-screen select-screen)
+(gv-define-simple-setter selected-frame select-frame)
+(gv-define-simple-setter standard-case-table set-standard-case-table)
+(gv-define-simple-setter syntax-table set-syntax-table)
+(gv-define-simple-setter visited-file-modtime set-visited-file-modtime t)
+(gv-define-setter window-height (store)
`(progn (enlarge-window (- ,store (window-height))) ,store))
-(cl-defsetf window-hscroll set-window-hscroll)
-(cl-defsetf window-parameter set-window-parameter)
-(cl-defsetf window-point set-window-point)
-(cl-defsetf window-start set-window-start)
-(cl-defsetf window-width () (store)
+(gv-define-setter window-width (store)
`(progn (enlarge-window (- ,store (window-width)) t) ,store))
-(cl-defsetf x-get-secondary-selection x-own-secondary-selection t)
-(cl-defsetf x-get-selection x-own-selection t)
+(gv-define-simple-setter x-get-secondary-selection x-own-secondary-selection t)
+(gv-define-simple-setter x-get-selection x-own-selection t)
-;; This is a hack that allows (cl-setf (eq a 7) B) to mean either
+;;; More complex setf-methods.
+
+;; This is a hack that allows (setf (eq a 7) B) to mean either
;; (setq a 7) or (setq a nil) depending on whether B is nil or not.
;; This is useful when you have control over the PLACE but not over
;; the VALUE, as is the case in define-minor-mode's :variable.
-(cl-define-setf-expander eq (place val)
- (let ((method (cl-get-setf-method place macroexpand-all-environment))
- (val-temp (make-symbol "--eq-val--"))
- (store-temp (make-symbol "--eq-store--")))
- (list (append (nth 0 method) (list val-temp))
- (append (nth 1 method) (list val))
- (list store-temp)
- `(let ((,(car (nth 2 method))
- (if ,store-temp ,val-temp (not ,val-temp))))
- ,(nth 3 method) ,store-temp)
- `(eq ,(nth 4 method) ,val-temp))))
-
-;;; More complex setf-methods.
-;; These should take &environment arguments, but since full arglists aren't
-;; available while compiling cl-macs, we fake it by referring to the global
-;; variable macroexpand-all-environment directly.
-
-(cl-define-setf-expander apply (func arg1 &rest rest)
- (or (and (memq (car-safe func) '(quote function cl-function))
- (symbolp (car-safe (cdr-safe func))))
- (error "First arg to apply in cl-setf is not (function SYM): %s" func))
- (let* ((form (cons (nth 1 func) (cons arg1 rest)))
- (method (cl-get-setf-method form macroexpand-all-environment)))
- (list (car method) (nth 1 method) (nth 2 method)
- (cl-setf-make-apply (nth 3 method) (cadr func) (car method))
- (cl-setf-make-apply (nth 4 method) (cadr func) (car method)))))
-
-(defun cl-setf-make-apply (form func temps)
- (if (eq (car form) 'progn)
- `(progn ,(cl-setf-make-apply (cadr form) func temps) ,@(cddr form))
- (or (equal (last form) (last temps))
- (error "%s is not suitable for use with setf-of-apply" func))
- `(apply ',(car form) ,@(cdr form))))
-
-(cl-define-setf-expander nthcdr (n place)
- (let ((method (cl-get-setf-method place macroexpand-all-environment))
- (n-temp (make-symbol "--cl-nthcdr-n--"))
- (store-temp (make-symbol "--cl-nthcdr-store--")))
- (list (cons n-temp (car method))
- (cons n (nth 1 method))
- (list store-temp)
- `(let ((,(car (nth 2 method))
- (cl--set-nthcdr ,n-temp ,(nth 4 method)
- ,store-temp)))
- ,(nth 3 method) ,store-temp)
- `(nthcdr ,n-temp ,(nth 4 method)))))
-
-(cl-define-setf-expander cl-getf (place tag &optional def)
- (let ((method (cl-get-setf-method place macroexpand-all-environment))
- (tag-temp (make-symbol "--cl-getf-tag--"))
- (def-temp (make-symbol "--cl-getf-def--"))
- (store-temp (make-symbol "--cl-getf-store--")))
- (list (append (car method) (list tag-temp def-temp))
- (append (nth 1 method) (list tag def))
- (list store-temp)
- `(let ((,(car (nth 2 method))
- (cl--set-getf ,(nth 4 method) ,tag-temp ,store-temp)))
- ,(nth 3 method) ,store-temp)
- `(cl-getf ,(nth 4 method) ,tag-temp ,def-temp))))
-
-(cl-define-setf-expander substring (place from &optional to)
- (let ((method (cl-get-setf-method place macroexpand-all-environment))
- (from-temp (make-symbol "--cl-substring-from--"))
- (to-temp (make-symbol "--cl-substring-to--"))
- (store-temp (make-symbol "--cl-substring-store--")))
- (list (append (car method) (list from-temp to-temp))
- (append (nth 1 method) (list from to))
- (list store-temp)
- `(let ((,(car (nth 2 method))
- (cl--set-substring ,(nth 4 method)
- ,from-temp ,to-temp ,store-temp)))
- ,(nth 3 method) ,store-temp)
- `(substring ,(nth 4 method) ,from-temp ,to-temp))))
-
-;;; Getting and optimizing setf-methods.
-;;;###autoload
-(defun cl-get-setf-method (place &optional env)
- "Return a list of five values describing the setf-method for PLACE.
-PLACE may be any Lisp form which can appear as the PLACE argument to
-a macro like `cl-setf' or `cl-incf'."
- (if (symbolp place)
- (let ((temp (make-symbol "--cl-setf--")))
- (list nil nil (list temp) `(setq ,place ,temp) place))
- (or (and (symbolp (car place))
- (let* ((func (car place))
- (name (symbol-name func))
- (method (get func 'setf-method))
- (case-fold-search nil))
- (or (and method
- (let ((macroexpand-all-environment env))
- (setq method (apply method (cdr place))))
- (if (and (consp method) (= (length method) 5))
- method
- (error "Setf-method for %s returns malformed method"
- func)))
- (and (string-match-p "\\`c[ad][ad][ad]?[ad]?r\\'" name)
- (cl-get-setf-method (cl-compiler-macroexpand place)))
- (and (eq func 'edebug-after)
- (cl-get-setf-method (nth (1- (length place)) place)
- env)))))
- (if (eq place (setq place (macroexpand place env)))
- (if (and (symbolp (car place)) (fboundp (car place))
- (symbolp (symbol-function (car place))))
- (cl-get-setf-method (cons (symbol-function (car place))
- (cdr place)) env)
- (error "No setf-method known for %s" (car place)))
- (cl-get-setf-method place env)))))
-
-(defun cl-setf-do-modify (place opt-expr)
- (let* ((method (cl-get-setf-method place macroexpand-all-environment))
- (temps (car method)) (values (nth 1 method))
- (lets nil) (subs nil)
- (optimize (and (not (eq opt-expr 'no-opt))
- (or (and (not (eq opt-expr 'unsafe))
- (cl--safe-expr-p opt-expr))
- (cl-setf-simple-store-p (car (nth 2 method))
- (nth 3 method)))))
- (simple (and optimize (consp place) (cl--simple-exprs-p (cdr place)))))
- (while values
- (if (or simple (macroexp-const-p (car values)))
- (push (cons (pop temps) (pop values)) subs)
- (push (list (pop temps) (pop values)) lets)))
- (list (nreverse lets)
- (cons (car (nth 2 method)) (cl-sublis subs (nth 3 method)))
- (cl-sublis subs (nth 4 method)))))
-
-(defun cl-setf-do-store (spec val)
- (let ((sym (car spec))
- (form (cdr spec)))
- (if (or (macroexp-const-p val)
- (and (cl--simple-expr-p val) (eq (cl--expr-contains form sym) 1))
- (cl-setf-simple-store-p sym form))
- (cl-subst val sym form)
- `(let ((,sym ,val)) ,form))))
-
-(defun cl-setf-simple-store-p (sym form)
- (and (consp form) (eq (cl--expr-contains form sym) 1)
- (eq (nth (1- (length form)) form) sym)
- (symbolp (car form)) (fboundp (car form))
- (not (eq (car-safe (symbol-function (car form))) 'macro))))
+;; It turned out that :variable needed more flexibility anyway, so
+;; this doesn't seem too useful now.
+(gv-define-expander eq
+ (lambda (do place val)
+ (gv-letplace (getter setter) place
+ (macroexp-let2 nil val val
+ (funcall do `(eq ,getter ,val)
+ (lambda (v)
+ `(cond
+ (,v ,(funcall setter val))
+ ((eq ,getter ,val) ,(funcall setter `(not ,val))))))))))
+
+(gv-define-expander nthcdr
+ (lambda (do n place)
+ (macroexp-let2 nil idx n
+ (gv-letplace (getter setter) place
+ (funcall do `(nthcdr ,idx ,getter)
+ (lambda (v) `(if (<= ,idx 0) ,(funcall setter v)
+ (setcdr (nthcdr (1- ,idx) ,getter) ,v))))))))
+
+(gv-define-expander cl-getf
+ (lambda (do place tag &optional def)
+ (gv-letplace (getter setter) place
+ (macroexp-let2 nil k tag
+ (macroexp-let2 nil d def
+ (funcall do `(cl-getf ,getter ,k ,d)
+ (lambda (v) (funcall setter `(cl--set-getf ,getter ,k ,v)))))))))
+
+(gv-define-expander substring
+ (lambda (do place from &optional to)
+ (gv-letplace (getter setter) place
+ (macroexp-let2 nil start from
+ (macroexp-let2 nil end to
+ (funcall do `(substring ,getter ,start ,end)
+ (lambda (v)
+ (funcall setter `(cl--set-substring
+ ,getter ,start ,end ,v)))))))))
;;; The standard modify macros.
-;;;###autoload
-(defmacro cl-setf (&rest args)
- "Set each PLACE to the value of its VAL.
-This is a generalized version of `setq'; the PLACEs may be symbolic
-references such as (car x) or (aref x i), as well as plain symbols.
-For example, (cl-setf (cl-cadar x) y) is equivalent to (setcar (cdar x) y).
-The return value is the last VAL in the list.
-\(fn PLACE VAL PLACE VAL ...)"
- (declare (debug (&rest [place form])))
- (if (cdr (cdr args))
- (let ((sets nil))
- (while args (push `(cl-setf ,(pop args) ,(pop args)) sets))
- (cons 'progn (nreverse sets)))
- (if (symbolp (car args))
- (and args (cons 'setq args))
- (let* ((method (cl-setf-do-modify (car args) (nth 1 args)))
- (store (cl-setf-do-store (nth 1 method) (nth 1 args))))
- (if (car method) `(let* ,(car method) ,store) store)))))
+;; `setf' is now part of core Elisp, defined in gv.el.
;;;###autoload
(defmacro cl-psetf (&rest args)
"Set PLACEs to the values VALs in parallel.
-This is like `cl-setf', except that all VAL forms are evaluated (in order)
+This is like `setf', except that all VAL forms are evaluated (in order)
before assigning any PLACEs to the corresponding values.
\(fn PLACE VAL PLACE VAL ...)"
- (declare (debug cl-setf))
+ (declare (debug setf))
(let ((p args) (simple t) (vars nil))
(while p
(if (or (not (symbolp (car p))) (cl--expr-depends-p (nth 1 p) vars))
(or p (error "Odd number of arguments to cl-psetf"))
(pop p))
(if simple
- `(progn (cl-setf ,@args) nil)
+ `(progn (setf ,@args) nil)
(setq args (reverse args))
- (let ((expr `(cl-setf ,(cadr args) ,(car args))))
+ (let ((expr `(setf ,(cadr args) ,(car args))))
(while (setq args (cddr args))
- (setq expr `(cl-setf ,(cadr args) (prog1 ,(car args) ,expr))))
+ (setq expr `(setf ,(cadr args) (prog1 ,(car args) ,expr))))
`(progn ,expr nil)))))
-;;;###autoload
-(defun cl-do-pop (place)
- (if (cl--simple-expr-p place)
- `(prog1 (car ,place) (cl-setf ,place (cdr ,place)))
- (let* ((method (cl-setf-do-modify place t))
- (temp (make-symbol "--cl-pop--")))
- `(let* (,@(car method)
- (,temp ,(nth 2 method)))
- (prog1 (car ,temp)
- ,(cl-setf-do-store (nth 1 method) `(cdr ,temp)))))))
-
;;;###autoload
(defmacro cl-remf (place tag)
"Remove TAG from property list PLACE.
-PLACE may be a symbol, or any generalized variable allowed by `cl-setf'.
+PLACE may be a symbol, or any generalized variable allowed by `setf'.
The form returns true if TAG was found and removed, nil otherwise."
(declare (debug (place form)))
- (let* ((method (cl-setf-do-modify place t))
- (tag-temp (and (not (macroexp-const-p tag)) (make-symbol "--cl-remf-tag--")))
- (val-temp (and (not (cl--simple-expr-p place))
- (make-symbol "--cl-remf-place--")))
- (ttag (or tag-temp tag))
- (tval (or val-temp (nth 2 method))))
- `(let* (,@(car method)
- ,@(and val-temp `((,val-temp ,(nth 2 method))))
- ,@(and tag-temp `((,tag-temp ,tag))))
- (if (eq ,ttag (car ,tval))
- (progn ,(cl-setf-do-store (nth 1 method) `(cddr ,tval))
+ (gv-letplace (tval setter) place
+ (macroexp-let2 macroexp-copyable-p ttag tag
+ `(if (eq ,ttag (car ,tval))
+ (progn ,(funcall setter `(cddr ,tval))
t)
(cl--do-remf ,tval ,ttag)))))
(defmacro cl-shiftf (place &rest args)
"Shift left among PLACEs.
Example: (cl-shiftf A B C) sets A to B, B to C, and returns the old A.
-Each PLACE may be a symbol, or any generalized variable allowed by `cl-setf'.
+Each PLACE may be a symbol, or any generalized variable allowed by `setf'.
\(fn PLACE... VAL)"
(declare (debug (&rest place)))
((null args) place)
((symbolp place) `(prog1 ,place (setq ,place (cl-shiftf ,@args))))
(t
- (let ((method (cl-setf-do-modify place 'unsafe)))
- `(let* ,(car method)
- (prog1 ,(nth 2 method)
- ,(cl-setf-do-store (nth 1 method) `(cl-shiftf ,@args))))))))
+ (gv-letplace (getter setter) place
+ `(prog1 ,getter
+ ,(funcall setter `(cl-shiftf ,@args)))))))
;;;###autoload
(defmacro cl-rotatef (&rest args)
"Rotate left among PLACEs.
Example: (cl-rotatef A B C) sets A to B, B to C, and C to A. It returns nil.
-Each PLACE may be a symbol, or any generalized variable allowed by `cl-setf'.
+Each PLACE may be a symbol, or any generalized variable allowed by `setf'.
\(fn PLACE...)"
(declare (debug (&rest place)))
(temp (make-symbol "--cl-rotatef--"))
(form temp))
(while (cdr places)
- (let ((method (cl-setf-do-modify (pop places) 'unsafe)))
- (setq form `(let* ,(car method)
- (prog1 ,(nth 2 method)
- ,(cl-setf-do-store (nth 1 method) form))))))
- (let ((method (cl-setf-do-modify (car places) 'unsafe)))
- `(let* (,@(car method) (,temp ,(nth 2 method)))
- ,(cl-setf-do-store (nth 1 method) form) nil)))))
-
-;;;###autoload
-(defmacro cl-letf (bindings &rest body)
- "Temporarily bind to PLACEs.
-This is the analogue of `let', but with generalized variables (in the
-sense of `cl-setf') for the PLACEs. Each PLACE is set to the corresponding
-VALUE, then the BODY forms are executed. On exit, either normally or
-because of a `throw' or error, the PLACEs are set back to their original
-values. Note that this macro is *not* available in Common Lisp.
-As a special case, if `(PLACE)' is used instead of `(PLACE VALUE)',
-the PLACE is not modified before executing BODY.
-
-\(fn ((PLACE VALUE) ...) BODY...)"
- (declare (indent 1) (debug ((&rest (gate place &optional form)) body)))
- (if (and (not (cdr bindings)) (cdar bindings) (symbolp (caar bindings)))
- `(let ,bindings ,@body)
- (let ((lets nil)
- (rev (reverse bindings)))
- (while rev
- (let* ((place (if (symbolp (caar rev))
- `(symbol-value ',(caar rev))
- (caar rev)))
- (value (cl-cadar rev))
- (method (cl-setf-do-modify place 'no-opt))
- (save (make-symbol "--cl-letf-save--"))
- (bound (and (memq (car place) '(symbol-value symbol-function))
- (make-symbol "--cl-letf-bound--")))
- (temp (and (not (macroexp-const-p value)) (cdr bindings)
- (make-symbol "--cl-letf-val--"))))
- (setq lets (nconc (car method)
- (if bound
- (list (list bound
- (list (if (eq (car place)
- 'symbol-value)
- 'boundp 'fboundp)
- (nth 1 (nth 2 method))))
- (list save `(and ,bound
- ,(nth 2 method))))
- (list (list save (nth 2 method))))
- (and temp (list (list temp value)))
- lets)
- body (list
- `(unwind-protect
- (progn
- ,@(if (cdr (car rev))
- (cons (cl-setf-do-store (nth 1 method)
- (or temp value))
- body)
- body))
- ,(if bound
- `(if ,bound
- ,(cl-setf-do-store (nth 1 method) save)
- (,(if (eq (car place) 'symbol-value)
- #'makunbound #'fmakunbound)
- ,(nth 1 (nth 2 method))))
- (cl-setf-do-store (nth 1 method) save))))
- rev (cdr rev))))
- `(let* ,lets ,@body))))
-
-
-;;;###autoload
-(defmacro cl-letf* (bindings &rest body)
- "Temporarily bind to PLACEs.
-This is the analogue of `let*', but with generalized variables (in the
-sense of `cl-setf') for the PLACEs. Each PLACE is set to the corresponding
-VALUE, then the BODY forms are executed. On exit, either normally or
-because of a `throw' or error, the PLACEs are set back to their original
-values. Note that this macro is *not* available in Common Lisp.
-As a special case, if `(PLACE)' is used instead of `(PLACE VALUE)',
-the PLACE is not modified before executing BODY.
-
-\(fn ((PLACE VALUE) ...) BODY...)"
- (declare (indent 1) (debug cl-letf))
- (if (null bindings)
- (cons 'progn body)
- (setq bindings (reverse bindings))
- (while bindings
- (setq body (list `(cl-letf (,(pop bindings)) ,@body))))
- (car body)))
+ (setq form
+ (gv-letplace (getter setter) (pop places)
+ `(prog1 ,getter ,(funcall setter form)))))
+ (gv-letplace (getter setter) (car places)
+ (macroexp-let* `((,temp ,getter))
+ `(progn ,(funcall setter form) nil))))))
;;;###autoload
(defmacro cl-callf (func place &rest args)
"Set PLACE to (FUNC PLACE ARGS...).
FUNC should be an unquoted function name. PLACE may be a symbol,
-or any generalized variable allowed by `cl-setf'.
-
-\(fn FUNC PLACE ARGS...)"
+or any generalized variable allowed by `setf'."
(declare (indent 2) (debug (cl-function place &rest form)))
- (let* ((method (cl-setf-do-modify place (cons 'list args)))
- (rargs (cons (nth 2 method) args)))
- `(let* ,(car method)
- ,(cl-setf-do-store (nth 1 method)
- (if (symbolp func) (cons func rargs)
- `(funcall #',func ,@rargs))))))
+ (gv-letplace (getter setter) place
+ (let* ((rargs (cons getter args)))
+ (funcall setter
+ (if (symbolp func) (cons func rargs)
+ `(funcall #',func ,@rargs))))))
;;;###autoload
(defmacro cl-callf2 (func arg1 place &rest args)
\(fn FUNC ARG1 PLACE ARGS...)"
(declare (indent 3) (debug (cl-function form place &rest form)))
(if (and (cl--safe-expr-p arg1) (cl--simple-expr-p place) (symbolp func))
- `(cl-setf ,place (,func ,arg1 ,place ,@args))
- (let* ((method (cl-setf-do-modify place (cons 'list args)))
- (temp (and (not (macroexp-const-p arg1)) (make-symbol "--cl-arg1--")))
- (rargs (cl-list* (or temp arg1) (nth 2 method) args)))
- `(let* (,@(and temp (list (list temp arg1))) ,@(car method))
- ,(cl-setf-do-store (nth 1 method)
- (if (symbolp func) (cons func rargs)
- `(funcall #',func ,@rargs)))))))
-
-;;;###autoload
-(defmacro cl-define-modify-macro (name arglist func &optional doc)
- "Define a `cl-setf'-like modify macro.
-If NAME is called, it combines its PLACE argument with the other arguments
-from ARGLIST using FUNC: (cl-define-modify-macro cl-incf (&optional (n 1)) +)"
- (declare (debug
- (&define name cl-lambda-list ;; should exclude &key
- symbolp &optional stringp)))
- (if (memq '&key arglist) (error "&key not allowed in cl-define-modify-macro"))
- (let ((place (make-symbol "--cl-place--")))
- `(cl-defmacro ,name (,place ,@arglist)
- ,doc
- (,(if (memq '&rest arglist) #'cl-list* #'list)
- #'cl-callf ',func ,place
- ,@(cl--arglist-args arglist)))))
-
+ `(setf ,place (,func ,arg1 ,place ,@args))
+ (macroexp-let2 nil a1 arg1
+ (gv-letplace (getter setter) place
+ (let* ((rargs (cl-list* a1 getter args)))
+ (funcall setter
+ (if (symbolp func) (cons func rargs)
+ `(funcall #',func ,@rargs))))))))
;;; Structures.
This macro defines a new data type called NAME that stores data
in SLOTs. It defines a `make-NAME' constructor, a `copy-NAME'
copier, a `NAME-p' predicate, and slot accessors named `NAME-SLOT'.
-You can use the accessors to set the corresponding slots, via `cl-setf'.
+You can use the accessors to set the corresponding slots, via `setf'.
NAME may instead take the form (NAME OPTIONS...), where each
OPTION is either a single keyword or (KEYWORD VALUE).
Each SLOT may instead take the form (SLOT SLOT-OPTS...), where
SLOT-OPTS are keyword-value pairs for that slot. Currently, only
one keyword is supported, `:read-only'. If this has a non-nil
-value, that slot cannot be set via `cl-setf'.
+value, that slot cannot be set via `setf'.
\(fn NAME SLOTS...)"
(declare (doc-string 2)
(let ((accessor (intern (format "%s%s" conc-name slot))))
(push slot slots)
(push (nth 1 desc) defaults)
- (push (cl-list*
- 'cl-defsubst accessor '(cl-x)
- (append
- (and pred-check
+ (push `(cl-defsubst ,accessor (cl-x)
+ ,@(and pred-check
(list `(or ,pred-check
(error "%s accessing a non-%s"
',accessor ',name))))
- (list (if (eq type 'vector) `(aref cl-x ,pos)
- (if (= pos 0) '(car cl-x)
- `(nth ,pos cl-x)))))) forms)
+ ,(if (eq type 'vector) `(aref cl-x ,pos)
+ (if (= pos 0) '(car cl-x)
+ `(nth ,pos cl-x)))) forms)
(push (cons accessor t) side-eff)
- (push `(cl-define-setf-expander ,accessor (cl-x)
- ,(if (cadr (memq :read-only (cddr desc)))
- `(progn (ignore cl-x)
- (error "%s is a read-only slot"
- ',accessor))
- ;; If cl is loaded only for compilation,
- ;; the call to cl-struct-setf-expander would
- ;; cause a warning because it may not be
- ;; defined at run time. Suppress that warning.
- `(progn
- (declare-function
- cl-struct-setf-expander "cl-macs"
- (x name accessor pred-form pos))
- (cl-struct-setf-expander
- cl-x ',name ',accessor
- ,(and pred-check `',pred-check)
- ,pos))))
- forms)
+ ;; Don't bother defining a setf-expander, since gv-get can use
+ ;; the compiler macro to get the same result.
+ ;;(push `(gv-define-setter ,accessor (cl-val cl-x)
+ ;; ,(if (cadr (memq :read-only (cddr desc)))
+ ;; `(progn (ignore cl-x cl-val)
+ ;; (error "%s is a read-only slot"
+ ;; ',accessor))
+ ;; ;; If cl is loaded only for compilation,
+ ;; ;; the call to cl--struct-setf-expander would
+ ;; ;; cause a warning because it may not be
+ ;; ;; defined at run time. Suppress that warning.
+ ;; `(progn
+ ;; (declare-function
+ ;; cl--struct-setf-expander "cl-macs"
+ ;; (x name accessor pred-form pos))
+ ;; (cl--struct-setf-expander
+ ;; cl-val cl-x ',name ',accessor
+ ;; ,(and pred-check `',pred-check)
+ ;; ,pos))))
+ ;; forms)
(if print-auto
(nconc print-func
(list `(princ ,(format " %s" slot) cl-s)
forms)
`(progn ,@(nreverse (cons `',name forms)))))
-;;;###autoload
-(defun cl-struct-setf-expander (x name accessor pred-form pos)
- (let* ((temp (make-symbol "--cl-x--")) (store (make-symbol "--cl-store--")))
- (list (list temp) (list x) (list store)
- `(progn
- ,@(and pred-form
- (list `(or ,(cl-subst temp 'cl-x pred-form)
- (error ,(format
- "%s storing a non-%s"
- accessor name)))))
- ,(if (eq (car (get name 'cl-struct-type)) 'vector)
- `(aset ,temp ,pos ,store)
- `(setcar
- ,(if (<= pos 5)
- (let ((xx temp))
- (while (>= (setq pos (1- pos)) 0)
- (setq xx `(cdr ,xx)))
- xx)
- `(nthcdr ,pos ,temp))
- ,store)))
- (list accessor temp))))
-
-
;;; Types and assertions.
;;;###autoload
surrounded by (cl-block NAME ...).
\(fn NAME ARGLIST [DOCSTRING] BODY...)"
- (declare (debug cl-defun))
+ (declare (debug cl-defun) (indent 2))
(let* ((argns (cl--arglist-args args)) (p argns)
(pbody (cons 'progn body))
(unsafe (not (cl--safe-expr-p pbody))))
(cl-define-compiler-macro cl-typep (&whole form val type)
(if (macroexp-const-p type)
- (macroexp-let² macroexp-copyable-p temp val
+ (macroexp-let2 macroexp-copyable-p temp val
(cl--make-type-test temp (cl--const-expr-val type)))
form))
(put y 'side-effect-free t))
;;; Things that are inline.
-(cl-proclaim '(inline cl-floatp-safe cl-acons cl-map cl-concatenate cl-notany cl-notevery
- cl--set-elt cl-revappend cl-nreconc gethash))
+(cl-proclaim '(inline cl-floatp-safe cl-acons cl-map cl-concatenate cl-notany
+ cl-notevery cl--set-elt cl-revappend cl-nreconc gethash))
;;; Things that are side-effect-free.
(mapc (lambda (x) (put x 'side-effect-free t))
\f
;;;### (autoloads (5x5-crack 5x5-crack-xor-mutate 5x5-crack-mutating-best
;;;;;; 5x5-crack-mutating-current 5x5-crack-randomly 5x5) "5x5"
-;;;;;; "play/5x5.el" (20355 10021))
+;;;;;; "play/5x5.el" (20244 35516))
;;; Generated autoloads from play/5x5.el
(autoload '5x5 "5x5" "\
;;;***
\f
;;;### (autoloads (ada-mode ada-add-extensions) "ada-mode" "progmodes/ada-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20428 57510))
;;; Generated autoloads from progmodes/ada-mode.el
(autoload 'ada-add-extensions "ada-mode" "\
;;;***
\f
;;;### (autoloads (ada-header) "ada-stmt" "progmodes/ada-stmt.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from progmodes/ada-stmt.el
(autoload 'ada-header "ada-stmt" "\
;;;***
\f
;;;### (autoloads (ada-find-file) "ada-xref" "progmodes/ada-xref.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from progmodes/ada-xref.el
(autoload 'ada-find-file "ada-xref" "\
;;;;;; add-change-log-entry-other-window add-change-log-entry find-change-log
;;;;;; prompt-for-change-log-name add-log-mailing-address add-log-full-name
;;;;;; add-log-current-defun-function) "add-log" "vc/add-log.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from vc/add-log.el
(put 'change-log-default-name 'safe-local-variable 'string-or-null-p)
\f
;;;### (autoloads (defadvice ad-activate ad-add-advice ad-disable-advice
;;;;;; ad-enable-advice ad-default-compilation-action ad-redefinition-action)
-;;;;;; "advice" "emacs-lisp/advice.el" (20355 10021))
+;;;;;; "advice" "emacs-lisp/advice.el" (20290 33419))
;;; Generated autoloads from emacs-lisp/advice.el
(defvar ad-redefinition-action 'warn "\
[DOCSTRING] [INTERACTIVE-FORM]
BODY...)
-\(fn FUNCTION ARGS &rest BODY)" nil (quote macro))
+\(fn FUNCTION ARGS &rest BODY)" nil t)
(put 'defadvice 'doc-string-elt '3)
\f
;;;### (autoloads (align-newline-and-indent align-unhighlight-rule
;;;;;; align-highlight-rule align-current align-entire align-regexp
-;;;;;; align) "align" "align.el" (20355 10021))
+;;;;;; align) "align" "align.el" (20244 35516))
;;; Generated autoloads from align.el
(autoload 'align "align" "\
\f
;;;### (autoloads (outlineify-sticky allout-mode allout-mode-p allout-auto-activation
;;;;;; allout-setup allout-auto-activation-helper) "allout" "allout.el"
-;;;;;; (20399 35365))
+;;;;;; (20412 11425))
;;; Generated autoloads from allout.el
(autoload 'allout-auto-activation-helper "allout" "\
(autoload 'allout-mode-p "allout" "\
Return t if `allout-mode' is active in current buffer.
-\(fn)" nil (quote macro))
+\(fn)" nil t)
(autoload 'allout-mode "allout" "\
Toggle Allout outline mode.
\f
;;;### (autoloads (allout-widgets-mode allout-widgets-auto-activation
;;;;;; allout-widgets-setup allout-widgets) "allout-widgets" "allout-widgets.el"
-;;;;;; (20385 23626))
+;;;;;; (20438 17064))
;;; Generated autoloads from allout-widgets.el
(let ((loads (get 'allout-widgets 'custom-loads))) (if (member '"allout-widgets" loads) nil (put 'allout-widgets 'custom-loads (cons '"allout-widgets" loads))))
;;;***
\f
;;;### (autoloads (ange-ftp-hook-function ange-ftp-reread-dir) "ange-ftp"
-;;;;;; "net/ange-ftp.el" (20373 11301))
+;;;;;; "net/ange-ftp.el" (20451 20881))
;;; Generated autoloads from net/ange-ftp.el
(defalias 'ange-ftp-re-read-dir 'ange-ftp-reread-dir)
;;;***
\f
;;;### (autoloads (animate-birthday-present animate-sequence animate-string)
-;;;;;; "animate" "play/animate.el" (20355 10021))
+;;;;;; "animate" "play/animate.el" (20356 35090))
;;; Generated autoloads from play/animate.el
(autoload 'animate-string "animate" "\
;;;***
\f
;;;### (autoloads (ansi-color-process-output ansi-color-for-comint-mode-on)
-;;;;;; "ansi-color" "ansi-color.el" (20394 17446))
+;;;;;; "ansi-color" "ansi-color.el" (20428 57510))
;;; Generated autoloads from ansi-color.el
(autoload 'ansi-color-for-comint-mode-on "ansi-color" "\
;;;***
\f
;;;### (autoloads (antlr-set-tabs antlr-mode antlr-show-makefile-rules)
-;;;;;; "antlr-mode" "progmodes/antlr-mode.el" (20355 10021))
+;;;;;; "antlr-mode" "progmodes/antlr-mode.el" (20428 57510))
;;; Generated autoloads from progmodes/antlr-mode.el
(autoload 'antlr-show-makefile-rules "antlr-mode" "\
;;;***
\f
;;;### (autoloads (appt-activate appt-add) "appt" "calendar/appt.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from calendar/appt.el
(autoload 'appt-add "appt" "\
\f
;;;### (autoloads (apropos-documentation apropos-value apropos-library
;;;;;; apropos apropos-documentation-property apropos-command apropos-variable
-;;;;;; apropos-read-pattern) "apropos" "apropos.el" (20374 32165))
+;;;;;; apropos-read-pattern) "apropos" "apropos.el" (20373 41604))
;;; Generated autoloads from apropos.el
(autoload 'apropos-read-pattern "apropos" "\
;;;***
\f
-;;;### (autoloads (archive-mode) "arc-mode" "arc-mode.el" (20387
-;;;;;; 44199))
+;;;### (autoloads (archive-mode) "arc-mode" "arc-mode.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from arc-mode.el
(autoload 'archive-mode "arc-mode" "\
;;;***
\f
-;;;### (autoloads (array-mode) "array" "array.el" (20355 10021))
+;;;### (autoloads (array-mode) "array" "array.el" (20244 35516))
;;; Generated autoloads from array.el
(autoload 'array-mode "array" "\
;;;***
\f
-;;;### (autoloads (artist-mode) "artist" "textmodes/artist.el" (20357
-;;;;;; 58785))
+;;;### (autoloads (artist-mode) "artist" "textmodes/artist.el" (20359
+;;;;;; 18671))
;;; Generated autoloads from textmodes/artist.el
(autoload 'artist-mode "artist" "\
;;;***
\f
-;;;### (autoloads (asm-mode) "asm-mode" "progmodes/asm-mode.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (asm-mode) "asm-mode" "progmodes/asm-mode.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from progmodes/asm-mode.el
(autoload 'asm-mode "asm-mode" "\
;;;***
\f
;;;### (autoloads (auth-source-cache-expiry) "auth-source" "gnus/auth-source.el"
-;;;;;; (20381 5411))
+;;;;;; (20428 57510))
;;; Generated autoloads from gnus/auth-source.el
(defvar auth-source-cache-expiry 7200 "\
;;;***
\f
;;;### (autoloads (autoarg-kp-mode autoarg-mode) "autoarg" "autoarg.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from autoarg.el
(defvar autoarg-mode nil "\
;;;***
\f
;;;### (autoloads (autoconf-mode) "autoconf" "progmodes/autoconf.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from progmodes/autoconf.el
(autoload 'autoconf-mode "autoconf" "\
;;;***
\f
;;;### (autoloads (auto-insert-mode define-auto-insert auto-insert)
-;;;;;; "autoinsert" "autoinsert.el" (20387 44199))
+;;;;;; "autoinsert" "autoinsert.el" (20412 11425))
;;; Generated autoloads from autoinsert.el
(autoload 'auto-insert "autoinsert" "\
\f
;;;### (autoloads (batch-update-autoloads update-directory-autoloads
;;;;;; update-file-autoloads) "autoload" "emacs-lisp/autoload.el"
-;;;;;; (20423 17700))
+;;;;;; (20446 34252))
;;; Generated autoloads from emacs-lisp/autoload.el
(put 'generated-autoload-file 'safe-local-variable 'stringp)
\f
;;;### (autoloads (global-auto-revert-mode turn-on-auto-revert-tail-mode
;;;;;; auto-revert-tail-mode turn-on-auto-revert-mode auto-revert-mode)
-;;;;;; "autorevert" "autorevert.el" (20373 11301))
+;;;;;; "autorevert" "autorevert.el" (20373 41604))
;;; Generated autoloads from autorevert.el
(autoload 'auto-revert-mode "autorevert" "\
;;;***
\f
;;;### (autoloads (mouse-avoidance-mode mouse-avoidance-mode) "avoid"
-;;;;;; "avoid.el" (20369 14251))
+;;;;;; "avoid.el" (20373 41604))
;;; Generated autoloads from avoid.el
(defvar mouse-avoidance-mode nil "\
;;;***
\f
;;;### (autoloads (display-battery-mode battery) "battery" "battery.el"
-;;;;;; (20369 14251))
+;;;;;; (20373 41604))
;;; Generated autoloads from battery.el
(put 'battery-mode-line-string 'risky-local-variable t)
;;;***
\f
;;;### (autoloads (benchmark benchmark-run-compiled benchmark-run)
-;;;;;; "benchmark" "emacs-lisp/benchmark.el" (20355 10021))
+;;;;;; "benchmark" "emacs-lisp/benchmark.el" (20244 35516))
;;; Generated autoloads from emacs-lisp/benchmark.el
(autoload 'benchmark-run "benchmark" "\
garbage collections that ran, and the time taken by garbage collection.
See also `benchmark-run-compiled'.
-\(fn &optional REPETITIONS &rest FORMS)" nil (quote macro))
+\(fn &optional REPETITIONS &rest FORMS)" nil t)
(autoload 'benchmark-run-compiled "benchmark" "\
Time execution of compiled version of FORMS.
byte code obtained by wrapping FORMS in a `lambda' and compiling the
result. The overhead of the `lambda's is accounted for.
-\(fn &optional REPETITIONS &rest FORMS)" nil (quote macro))
+\(fn &optional REPETITIONS &rest FORMS)" nil t)
(autoload 'benchmark "benchmark" "\
Print the time taken for REPETITIONS executions of FORM.
;;;***
\f
;;;### (autoloads (bibtex-search-entry bibtex-mode bibtex-initialize)
-;;;;;; "bibtex" "textmodes/bibtex.el" (20355 10021))
+;;;;;; "bibtex" "textmodes/bibtex.el" (20446 34252))
;;; Generated autoloads from textmodes/bibtex.el
(autoload 'bibtex-initialize "bibtex" "\
;;;***
\f
;;;### (autoloads (bibtex-style-mode) "bibtex-style" "textmodes/bibtex-style.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from textmodes/bibtex-style.el
(autoload 'bibtex-style-mode "bibtex-style" "\
\f
;;;### (autoloads (binhex-decode-region binhex-decode-region-external
;;;;;; binhex-decode-region-internal) "binhex" "mail/binhex.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from mail/binhex.el
(defconst binhex-begin-line "^:...............................................................$" "\
;;;***
\f
-;;;### (autoloads (blackbox) "blackbox" "play/blackbox.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (blackbox) "blackbox" "play/blackbox.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from play/blackbox.el
(autoload 'blackbox "blackbox" "\
;;;;;; bookmark-save bookmark-write bookmark-delete bookmark-insert
;;;;;; bookmark-rename bookmark-insert-location bookmark-relocate
;;;;;; bookmark-jump-other-window bookmark-jump bookmark-set) "bookmark"
-;;;;;; "bookmark.el" (20399 35365))
+;;;;;; "bookmark.el" (20412 11425))
;;; Generated autoloads from bookmark.el
(define-key ctl-x-r-map "b" 'bookmark-jump)
(define-key ctl-x-r-map "m" 'bookmark-set)
;;;;;; browse-url-xdg-open browse-url-at-mouse browse-url-at-point
;;;;;; browse-url browse-url-of-region browse-url-of-dired-file
;;;;;; browse-url-of-buffer browse-url-of-file browse-url-browser-function)
-;;;;;; "browse-url" "net/browse-url.el" (20395 3526))
+;;;;;; "browse-url" "net/browse-url.el" (20412 11425))
;;; Generated autoloads from net/browse-url.el
(defvar browse-url-browser-function 'browse-url-default-browser "\
;;;***
\f
;;;### (autoloads (bs-show bs-customize bs-cycle-previous bs-cycle-next)
-;;;;;; "bs" "bs.el" (20369 14251))
+;;;;;; "bs" "bs.el" (20373 41604))
;;; Generated autoloads from bs.el
(autoload 'bs-cycle-next "bs" "\
;;;***
\f
-;;;### (autoloads (bubbles) "bubbles" "play/bubbles.el" (20355 10021))
+;;;### (autoloads (bubbles) "bubbles" "play/bubbles.el" (20244 35516))
;;; Generated autoloads from play/bubbles.el
(autoload 'bubbles "bubbles" "\
;;;***
\f
;;;### (autoloads (bug-reference-prog-mode bug-reference-mode) "bug-reference"
-;;;;;; "progmodes/bug-reference.el" (20355 10021))
+;;;;;; "progmodes/bug-reference.el" (20244 35516))
;;; Generated autoloads from progmodes/bug-reference.el
(put 'bug-reference-url-format 'safe-local-variable (lambda (s) (or (stringp s) (and (symbolp s) (get s 'bug-reference-url-format)))))
;;;;;; batch-byte-compile-if-not-done display-call-tree byte-compile
;;;;;; compile-defun byte-compile-file byte-recompile-directory
;;;;;; byte-force-recompile byte-compile-enable-warning byte-compile-disable-warning)
-;;;;;; "bytecomp" "emacs-lisp/bytecomp.el" (20423 17700))
+;;;;;; "bytecomp" "emacs-lisp/bytecomp.el" (20451 21087))
;;; Generated autoloads from emacs-lisp/bytecomp.el
(put 'byte-compile-dynamic 'safe-local-variable 'booleanp)
(put 'byte-compile-disable-print-circle 'safe-local-variable 'booleanp)
;;;***
\f
-;;;### (autoloads nil "cal-china" "calendar/cal-china.el" (20355
-;;;;;; 10021))
+;;;### (autoloads nil "cal-china" "calendar/cal-china.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from calendar/cal-china.el
(put 'calendar-chinese-time-zone 'risky-local-variable t)
;;;***
\f
-;;;### (autoloads nil "cal-dst" "calendar/cal-dst.el" (20355 10021))
+;;;### (autoloads nil "cal-dst" "calendar/cal-dst.el" (20244 35516))
;;; Generated autoloads from calendar/cal-dst.el
(put 'calendar-daylight-savings-starts 'risky-local-variable t)
;;;***
\f
;;;### (autoloads (calendar-hebrew-list-yahrzeits) "cal-hebrew" "calendar/cal-hebrew.el"
-;;;;;; (20355 10021))
+;;;;;; (20290 33419))
;;; Generated autoloads from calendar/cal-hebrew.el
(autoload 'calendar-hebrew-list-yahrzeits "cal-hebrew" "\
\f
;;;### (autoloads (defmath calc-embedded-activate calc-embedded calc-grab-rectangle
;;;;;; calc-grab-region full-calc-keypad calc-keypad calc-eval quick-calc
-;;;;;; full-calc calc calc-dispatch) "calc" "calc/calc.el" (20407
-;;;;;; 29477))
+;;;;;; full-calc calc calc-dispatch) "calc" "calc/calc.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from calc/calc.el
(define-key ctl-x-map "*" 'calc-dispatch)
See Info node `(calc)Defining Functions'.
-\(fn FUNC ARGS &rest BODY)" nil (quote macro))
+\(fn FUNC ARGS &rest BODY)" nil t)
(put 'defmath 'doc-string-elt '3)
;;;***
\f
-;;;### (autoloads (calc-undo) "calc-undo" "calc/calc-undo.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (calc-undo) "calc-undo" "calc/calc-undo.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from calc/calc-undo.el
(autoload 'calc-undo "calc-undo" "\
;;;***
\f
-;;;### (autoloads (calculator) "calculator" "calculator.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (calculator) "calculator" "calculator.el" (20428
+;;;;;; 57510))
;;; Generated autoloads from calculator.el
(autoload 'calculator "calculator" "\
;;;***
\f
-;;;### (autoloads (calendar) "calendar" "calendar/calendar.el" (20388
-;;;;;; 65061))
+;;;### (autoloads (calendar) "calendar" "calendar/calendar.el" (20432
+;;;;;; 42254))
;;; Generated autoloads from calendar/calendar.el
(autoload 'calendar "calendar" "\
;;;***
\f
;;;### (autoloads (canlock-verify canlock-insert-header) "canlock"
-;;;;;; "gnus/canlock.el" (20355 10021))
+;;;;;; "gnus/canlock.el" (20244 35516))
;;; Generated autoloads from gnus/canlock.el
(autoload 'canlock-insert-header "canlock" "\
;;;***
\f
;;;### (autoloads (capitalized-words-mode) "cap-words" "progmodes/cap-words.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from progmodes/cap-words.el
(autoload 'capitalized-words-mode "cap-words" "\
;;;***
\f
-;;;### (autoloads nil "cc-compat" "progmodes/cc-compat.el" (20355
-;;;;;; 10021))
+;;;### (autoloads nil "cc-compat" "progmodes/cc-compat.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from progmodes/cc-compat.el
(put 'c-indent-level 'safe-local-variable 'integerp)
;;;***
\f
;;;### (autoloads (c-guess-basic-syntax) "cc-engine" "progmodes/cc-engine.el"
-;;;;;; (20373 11301))
+;;;;;; (20373 41604))
;;; Generated autoloads from progmodes/cc-engine.el
(autoload 'c-guess-basic-syntax "cc-engine" "\
\f
;;;### (autoloads (c-guess-install c-guess-region-no-install c-guess-region
;;;;;; c-guess-buffer-no-install c-guess-buffer c-guess-no-install
-;;;;;; c-guess) "cc-guess" "progmodes/cc-guess.el" (20355 10021))
+;;;;;; c-guess) "cc-guess" "progmodes/cc-guess.el" (20276 3849))
;;; Generated autoloads from progmodes/cc-guess.el
(defvar c-guess-guessed-offsets-alist nil "\
\f
;;;### (autoloads (awk-mode pike-mode idl-mode java-mode objc-mode
;;;;;; c++-mode c-mode c-initialize-cc-mode) "cc-mode" "progmodes/cc-mode.el"
-;;;;;; (20416 44451))
+;;;;;; (20419 46656))
;;; Generated autoloads from progmodes/cc-mode.el
(autoload 'c-initialize-cc-mode "cc-mode" "\
;;;***
\f
;;;### (autoloads (c-set-offset c-add-style c-set-style) "cc-styles"
-;;;;;; "progmodes/cc-styles.el" (20355 10021))
+;;;;;; "progmodes/cc-styles.el" (20244 35516))
;;; Generated autoloads from progmodes/cc-styles.el
(autoload 'c-set-style "cc-styles" "\
;;;***
\f
-;;;### (autoloads nil "cc-vars" "progmodes/cc-vars.el" (20355 10021))
+;;;### (autoloads nil "cc-vars" "progmodes/cc-vars.el" (20290 33419))
;;; Generated autoloads from progmodes/cc-vars.el
(put 'c-basic-offset 'safe-local-variable 'integerp)
(put 'c-backslash-column 'safe-local-variable 'integerp)
\f
;;;### (autoloads (ccl-execute-with-args check-ccl-program define-ccl-program
;;;;;; declare-ccl-program ccl-dump ccl-compile) "ccl" "international/ccl.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from international/ccl.el
(autoload 'ccl-compile "ccl" "\
Optional arg VECTOR is a compiled CCL code of the CCL program.
-\(fn NAME &optional VECTOR)" nil (quote macro))
+\(fn NAME &optional VECTOR)" nil t)
(autoload 'define-ccl-program "ccl" "\
Set NAME the compiled code of CCL-PROGRAM.
MAP-SET := MAP-IDs | (MAP-IDs) MAP-SET
MAP-ID := integer
-\(fn NAME CCL-PROGRAM &optional DOC)" nil (quote macro))
+\(fn NAME CCL-PROGRAM &optional DOC)" nil t)
(put 'define-ccl-program 'doc-string-elt '3)
If CCL-PROGRAM is a vector and optional arg NAME (symbol) is supplied,
register CCL-PROGRAM by name NAME, and return NAME.
-\(fn CCL-PROGRAM &optional NAME)" nil (quote macro))
+\(fn CCL-PROGRAM &optional NAME)" nil t)
(autoload 'ccl-execute-with-args "ccl" "\
Execute CCL-PROGRAM with registers initialized by the remaining args.
;;;***
\f
;;;### (autoloads (cconv-closure-convert) "cconv" "emacs-lisp/cconv.el"
-;;;;;; (20421 62373))
+;;;;;; (20451 21087))
;;; Generated autoloads from emacs-lisp/cconv.el
(autoload 'cconv-closure-convert "cconv" "\
;;;***
\f
;;;### (autoloads (cfengine-auto-mode cfengine2-mode cfengine3-mode)
-;;;;;; "cfengine" "progmodes/cfengine.el" (20355 10021))
+;;;;;; "cfengine" "progmodes/cfengine.el" (20356 35090))
;;; Generated autoloads from progmodes/cfengine.el
(autoload 'cfengine3-mode "cfengine" "\
;;;***
\f
;;;### (autoloads (check-declare-directory check-declare-file) "check-declare"
-;;;;;; "emacs-lisp/check-declare.el" (20378 29222))
+;;;;;; "emacs-lisp/check-declare.el" (20380 26775))
;;; Generated autoloads from emacs-lisp/check-declare.el
(autoload 'check-declare-file "check-declare" "\
;;;;;; checkdoc-comments checkdoc-continue checkdoc-start checkdoc-current-buffer
;;;;;; checkdoc-eval-current-buffer checkdoc-message-interactive
;;;;;; checkdoc-interactive checkdoc checkdoc-list-of-strings-p)
-;;;;;; "checkdoc" "emacs-lisp/checkdoc.el" (20388 65061))
+;;;;;; "checkdoc" "emacs-lisp/checkdoc.el" (20412 11425))
;;; Generated autoloads from emacs-lisp/checkdoc.el
(put 'checkdoc-force-docstrings-flag 'safe-local-variable 'booleanp)
(put 'checkdoc-force-history-flag 'safe-local-variable 'booleanp)
\f
;;;### (autoloads (pre-write-encode-hz post-read-decode-hz encode-hz-buffer
;;;;;; encode-hz-region decode-hz-buffer decode-hz-region) "china-util"
-;;;;;; "language/china-util.el" (20355 10021))
+;;;;;; "language/china-util.el" (20244 35516))
;;; Generated autoloads from language/china-util.el
(autoload 'decode-hz-region "china-util" "\
;;;***
\f
;;;### (autoloads (command-history list-command-history repeat-matching-complex-command)
-;;;;;; "chistory" "chistory.el" (20355 10021))
+;;;;;; "chistory" "chistory.el" (20244 35516))
;;; Generated autoloads from chistory.el
(autoload 'repeat-matching-complex-command "chistory" "\
\(fn)" t nil)
-;;;***
-\f
-;;;### (autoloads nil "cl" "emacs-lisp/cl.el" (20406 8611))
-;;; Generated autoloads from emacs-lisp/cl.el
-
-(defvar custom-print-functions nil "\
-This is a list of functions that format user objects for printing.
-Each function is called in turn with three arguments: the object, the
-stream, and the print level (currently ignored). If it is able to
-print the object it returns true; otherwise it returns nil and the
-printer proceeds to the next function on the list.
-
-This variable is not used at present, but it is defined in hopes that
-a future Emacs interpreter will be able to use it.")
-
-(put 'defun* 'doc-string-elt 3)
-
-(put 'defmacro* 'doc-string-elt 3)
-
-(put 'defsubst 'doc-string-elt 3)
-
-(put 'defstruct 'doc-string-elt 2)
-
;;;***
\f
;;;### (autoloads (common-lisp-indent-function) "cl-indent" "emacs-lisp/cl-indent.el"
-;;;;;; (20355 10021))
+;;;;;; (20290 33419))
;;; Generated autoloads from emacs-lisp/cl-indent.el
(autoload 'common-lisp-indent-function "cl-indent" "\
\(fn INDENT-POINT STATE)" nil nil)
+;;;***
+\f
+;;;### (autoloads nil "cl-lib" "emacs-lisp/cl-lib.el" (20451 21087))
+;;; Generated autoloads from emacs-lisp/cl-lib.el
+
+(define-obsolete-variable-alias 'custom-print-functions 'cl-custom-print-functions "24.2")
+
+(defvar cl-custom-print-functions nil "\
+This is a list of functions that format user objects for printing.
+Each function is called in turn with three arguments: the object, the
+stream, and the print level (currently ignored). If it is able to
+print the object it returns true; otherwise it returns nil and the
+printer proceeds to the next function on the list.
+
+This variable is not used at present, but it is defined in hopes that
+a future Emacs interpreter will be able to use it.")
+
+(autoload 'cl--defsubst-expand "cl-macs")
+
+(put 'cl-defun 'doc-string-elt 3)
+
+(put 'cl-defmacro 'doc-string-elt 3)
+
+(put 'cl-defsubst 'doc-string-elt 3)
+
+(put 'cl-defstruct 'doc-string-elt 2)
+
;;;***
\f
;;;### (autoloads (c-macro-expand) "cmacexp" "progmodes/cmacexp.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from progmodes/cmacexp.el
(autoload 'c-macro-expand "cmacexp" "\
;;;***
\f
-;;;### (autoloads (run-scheme) "cmuscheme" "cmuscheme.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (run-scheme) "cmuscheme" "cmuscheme.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from cmuscheme.el
(autoload 'run-scheme "cmuscheme" "\
;;;***
\f
-;;;### (autoloads (color-name-to-rgb) "color" "color.el" (20355 10021))
+;;;### (autoloads (color-name-to-rgb) "color" "color.el" (20356 19083))
;;; Generated autoloads from color.el
(autoload 'color-name-to-rgb "color" "\
;;;### (autoloads (comint-redirect-results-list-from-process comint-redirect-results-list
;;;;;; comint-redirect-send-command-to-process comint-redirect-send-command
;;;;;; comint-run make-comint make-comint-in-buffer) "comint" "comint.el"
-;;;;;; (20420 41510))
+;;;;;; (20420 52684))
;;; Generated autoloads from comint.el
(defvar comint-output-filter-functions '(ansi-color-process-output comint-postoutput-scroll-to-bottom comint-watch-for-password-prompt) "\
;;;***
\f
;;;### (autoloads (compare-windows) "compare-w" "vc/compare-w.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from vc/compare-w.el
(autoload 'compare-windows "compare-w" "\
;;;;;; compilation-shell-minor-mode compilation-mode compilation-start
;;;;;; compile compilation-disable-input compile-command compilation-search-path
;;;;;; compilation-ask-about-save compilation-window-height compilation-start-hook
-;;;;;; compilation-mode-hook) "compile" "progmodes/compile.el" (20410
-;;;;;; 5673))
+;;;;;; compilation-mode-hook) "compile" "progmodes/compile.el" (20428
+;;;;;; 57510))
;;; Generated autoloads from progmodes/compile.el
(defvar compilation-mode-hook nil "\
;;;***
\f
;;;### (autoloads (dynamic-completion-mode) "completion" "completion.el"
-;;;;;; (20388 65061))
+;;;;;; (20412 11425))
;;; Generated autoloads from completion.el
(defvar dynamic-completion-mode nil "\
;;;### (autoloads (conf-xdefaults-mode conf-ppd-mode conf-colon-mode
;;;;;; conf-space-keywords conf-space-mode conf-javaprop-mode conf-windows-mode
;;;;;; conf-unix-mode conf-mode) "conf-mode" "textmodes/conf-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from textmodes/conf-mode.el
(autoload 'conf-mode "conf-mode" "\
;;;***
\f
;;;### (autoloads (shuffle-vector cookie-snarf cookie-insert cookie)
-;;;;;; "cookie1" "play/cookie1.el" (20364 27900))
+;;;;;; "cookie1" "play/cookie1.el" (20373 41604))
;;; Generated autoloads from play/cookie1.el
(autoload 'cookie "cookie1" "\
;;;***
\f
;;;### (autoloads (copyright-update-directory copyright copyright-fix-years
-;;;;;; copyright-update) "copyright" "emacs-lisp/copyright.el" (20387
-;;;;;; 44199))
+;;;;;; copyright-update) "copyright" "emacs-lisp/copyright.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from emacs-lisp/copyright.el
(put 'copyright-at-end-flag 'safe-local-variable 'booleanp)
(put 'copyright-names-regexp 'safe-local-variable 'stringp)
;;;***
\f
;;;### (autoloads (cperl-perldoc-at-point cperl-perldoc cperl-mode)
-;;;;;; "cperl-mode" "progmodes/cperl-mode.el" (20355 10021))
+;;;;;; "cperl-mode" "progmodes/cperl-mode.el" (20451 20950))
;;; Generated autoloads from progmodes/cperl-mode.el
(put 'cperl-indent-level 'safe-local-variable 'integerp)
(put 'cperl-brace-offset 'safe-local-variable 'integerp)
;;;***
\f
;;;### (autoloads (cpp-parse-edit cpp-highlight-buffer) "cpp" "progmodes/cpp.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from progmodes/cpp.el
(autoload 'cpp-highlight-buffer "cpp" "\
;;;***
\f
;;;### (autoloads (crisp-mode crisp-mode) "crisp" "emulation/crisp.el"
-;;;;;; (20355 10021))
+;;;;;; (20428 57510))
;;; Generated autoloads from emulation/crisp.el
(defvar crisp-mode nil "\
;;;***
\f
;;;### (autoloads (completing-read-multiple) "crm" "emacs-lisp/crm.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from emacs-lisp/crm.el
(autoload 'completing-read-multiple "crm" "\
;;;***
\f
-;;;### (autoloads (css-mode) "css-mode" "textmodes/css-mode.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (css-mode) "css-mode" "textmodes/css-mode.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from textmodes/css-mode.el
(autoload 'css-mode "css-mode" "\
;;;***
\f
;;;### (autoloads (cua-selection-mode cua-mode) "cua-base" "emulation/cua-base.el"
-;;;;;; (20361 20134))
+;;;;;; (20434 28080))
;;; Generated autoloads from emulation/cua-base.el
(defvar cua-mode nil "\
;;;;;; customize-mode customize customize-push-and-save customize-save-variable
;;;;;; customize-set-variable customize-set-value custom-menu-sort-alphabetically
;;;;;; custom-buffer-sort-alphabetically custom-browse-sort-alphabetically)
-;;;;;; "cus-edit" "cus-edit.el" (20399 35365))
+;;;;;; "cus-edit" "cus-edit.el" (20438 17064))
;;; Generated autoloads from cus-edit.el
(defvar custom-browse-sort-alphabetically nil "\
;;;***
\f
;;;### (autoloads (customize-themes describe-theme custom-theme-visit-theme
-;;;;;; customize-create-theme) "cus-theme" "cus-theme.el" (20355
-;;;;;; 10021))
+;;;;;; customize-create-theme) "cus-theme" "cus-theme.el" (20336
+;;;;;; 29137))
;;; Generated autoloads from cus-theme.el
(autoload 'customize-create-theme "cus-theme" "\
;;;***
\f
;;;### (autoloads (cvs-status-mode) "cvs-status" "vc/cvs-status.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from vc/cvs-status.el
(autoload 'cvs-status-mode "cvs-status" "\
;;;***
\f
;;;### (autoloads (global-cwarn-mode turn-on-cwarn-mode cwarn-mode)
-;;;;;; "cwarn" "progmodes/cwarn.el" (20355 10021))
+;;;;;; "cwarn" "progmodes/cwarn.el" (20446 34252))
;;; Generated autoloads from progmodes/cwarn.el
(autoload 'cwarn-mode "cwarn" "\
\f
;;;### (autoloads (standard-display-cyrillic-translit cyrillic-encode-alternativnyj-char
;;;;;; cyrillic-encode-koi8-r-char) "cyril-util" "language/cyril-util.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from language/cyril-util.el
(autoload 'cyrillic-encode-koi8-r-char "cyril-util" "\
;;;***
\f
;;;### (autoloads (dabbrev-expand dabbrev-completion) "dabbrev" "dabbrev.el"
-;;;;;; (20397 45851))
+;;;;;; (20412 11425))
;;; Generated autoloads from dabbrev.el
(put 'dabbrev-case-fold-search 'risky-local-variable t)
(put 'dabbrev-case-replace 'risky-local-variable t)
;;;***
\f
;;;### (autoloads (data-debug-new-buffer) "data-debug" "cedet/data-debug.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from cedet/data-debug.el
(autoload 'data-debug-new-buffer "data-debug" "\
;;;***
\f
-;;;### (autoloads (dbus-handle-event) "dbus" "net/dbus.el" (20399
-;;;;;; 35365))
+;;;### (autoloads (dbus-handle-event) "dbus" "net/dbus.el" (20446
+;;;;;; 34252))
;;; Generated autoloads from net/dbus.el
(autoload 'dbus-handle-event "dbus" "\
;;;***
\f
-;;;### (autoloads (dcl-mode) "dcl-mode" "progmodes/dcl-mode.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (dcl-mode) "dcl-mode" "progmodes/dcl-mode.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from progmodes/dcl-mode.el
(autoload 'dcl-mode "dcl-mode" "\
;;;***
\f
;;;### (autoloads (cancel-debug-on-entry debug-on-entry debug) "debug"
-;;;;;; "emacs-lisp/debug.el" (20355 10021))
+;;;;;; "emacs-lisp/debug.el" (20244 35516))
;;; Generated autoloads from emacs-lisp/debug.el
(setq debugger 'debug)
;;;***
\f
;;;### (autoloads (decipher-mode decipher) "decipher" "play/decipher.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from play/decipher.el
(autoload 'decipher "decipher" "\
;;;***
\f
;;;### (autoloads (delimit-columns-rectangle delimit-columns-region
-;;;;;; delimit-columns-customize) "delim-col" "delim-col.el" (20355
-;;;;;; 10021))
+;;;;;; delimit-columns-customize) "delim-col" "delim-col.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from delim-col.el
(autoload 'delimit-columns-customize "delim-col" "\
;;;***
\f
-;;;### (autoloads (delphi-mode) "delphi" "progmodes/delphi.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (delphi-mode) "delphi" "progmodes/delphi.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from progmodes/delphi.el
(autoload 'delphi-mode "delphi" "\
;;;***
\f
-;;;### (autoloads (delete-selection-mode) "delsel" "delsel.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (delete-selection-mode) "delsel" "delsel.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from delsel.el
(defalias 'pending-delete-mode 'delete-selection-mode)
;;;***
\f
;;;### (autoloads (derived-mode-init-mode-variables define-derived-mode)
-;;;;;; "derived" "emacs-lisp/derived.el" (20355 10021))
+;;;;;; "derived" "emacs-lisp/derived.el" (20438 17064))
;;; Generated autoloads from emacs-lisp/derived.el
(autoload 'define-derived-mode "derived" "\
See Info node `(elisp)Derived Modes' for more details.
-\(fn CHILD PARENT NAME &optional DOCSTRING &rest BODY)" nil (quote macro))
+\(fn CHILD PARENT NAME &optional DOCSTRING &rest BODY)" nil t)
(put 'define-derived-mode 'doc-string-elt '4)
;;;***
\f
;;;### (autoloads (describe-char describe-text-properties) "descr-text"
-;;;;;; "descr-text.el" (20369 14251))
+;;;;;; "descr-text.el" (20434 28080))
;;; Generated autoloads from descr-text.el
(autoload 'describe-text-properties "descr-text" "\
;;;### (autoloads (desktop-revert desktop-save-in-desktop-dir desktop-change-dir
;;;;;; desktop-load-default desktop-read desktop-remove desktop-save
;;;;;; desktop-clear desktop-locals-to-save desktop-save-mode) "desktop"
-;;;;;; "desktop.el" (20423 17700))
+;;;;;; "desktop.el" (20451 20881))
;;; Generated autoloads from desktop.el
(defvar desktop-save-mode nil "\
\f
;;;### (autoloads (gnus-article-outlook-deuglify-article gnus-outlook-deuglify-article
;;;;;; gnus-article-outlook-repair-attribution gnus-article-outlook-unwrap-lines)
-;;;;;; "deuglify" "gnus/deuglify.el" (20355 10021))
+;;;;;; "deuglify" "gnus/deuglify.el" (20244 35516))
;;; Generated autoloads from gnus/deuglify.el
(autoload 'gnus-article-outlook-unwrap-lines "deuglify" "\
;;;***
\f
;;;### (autoloads (diary-mode diary-mail-entries diary) "diary-lib"
-;;;;;; "calendar/diary-lib.el" (20355 10021))
+;;;;;; "calendar/diary-lib.el" (20290 33419))
;;; Generated autoloads from calendar/diary-lib.el
(autoload 'diary "diary-lib" "\
;;;***
\f
;;;### (autoloads (diff-buffer-with-file diff-backup diff diff-command
-;;;;;; diff-switches) "diff" "vc/diff.el" (20379 50083))
+;;;;;; diff-switches) "diff" "vc/diff.el" (20380 26775))
;;; Generated autoloads from vc/diff.el
(defvar diff-switches (purecopy "-c") "\
;;;***
\f
;;;### (autoloads (diff-minor-mode diff-mode) "diff-mode" "vc/diff-mode.el"
-;;;;;; (20415 23587))
+;;;;;; (20415 57974))
;;; Generated autoloads from vc/diff-mode.el
(autoload 'diff-mode "diff-mode" "\
;;;***
\f
-;;;### (autoloads (dig) "dig" "net/dig.el" (20355 10021))
+;;;### (autoloads (dig) "dig" "net/dig.el" (20244 35516))
;;; Generated autoloads from net/dig.el
(autoload 'dig "dig" "\
;;;***
\f
;;;### (autoloads (dired-mode dired-noselect dired-other-frame dired-other-window
-;;;;;; dired dired-listing-switches) "dired" "dired.el" (20399 35754))
+;;;;;; dired dired-listing-switches) "dired" "dired.el" (20428 57510))
;;; Generated autoloads from dired.el
(defvar dired-listing-switches (purecopy "-al") "\
;;;***
\f
;;;### (autoloads (dirtrack dirtrack-mode) "dirtrack" "dirtrack.el"
-;;;;;; (20399 35365))
+;;;;;; (20412 11425))
;;; Generated autoloads from dirtrack.el
(autoload 'dirtrack-mode "dirtrack" "\
;;;***
\f
-;;;### (autoloads (disassemble) "disass" "emacs-lisp/disass.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (disassemble) "disass" "emacs-lisp/disass.el" (20432
+;;;;;; 64735))
;;; Generated autoloads from emacs-lisp/disass.el
(autoload 'disassemble "disass" "\
;;;;;; standard-display-g1 standard-display-ascii standard-display-default
;;;;;; standard-display-8bit describe-current-display-table describe-display-table
;;;;;; set-display-table-slot display-table-slot make-display-table)
-;;;;;; "disp-table" "disp-table.el" (20355 10021))
+;;;;;; "disp-table" "disp-table.el" (20244 35516))
;;; Generated autoloads from disp-table.el
(autoload 'make-display-table "disp-table" "\
;;;***
\f
;;;### (autoloads (dissociated-press) "dissociate" "play/dissociate.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from play/dissociate.el
(autoload 'dissociated-press "dissociate" "\
;;;***
\f
-;;;### (autoloads (dnd-protocol-alist) "dnd" "dnd.el" (20355 10021))
+;;;### (autoloads (dnd-protocol-alist) "dnd" "dnd.el" (20244 35516))
;;; Generated autoloads from dnd.el
(defvar dnd-protocol-alist `((,(purecopy "^file:///") . dnd-open-local-file) (,(purecopy "^file://") . dnd-open-file) (,(purecopy "^file:") . dnd-open-local-file) (,(purecopy "^\\(https?\\|ftp\\|file\\|nfs\\)://") . dnd-open-file)) "\
;;;***
\f
;;;### (autoloads (dns-mode-soa-increment-serial dns-mode) "dns-mode"
-;;;;;; "textmodes/dns-mode.el" (20355 10021))
+;;;;;; "textmodes/dns-mode.el" (20244 35516))
;;; Generated autoloads from textmodes/dns-mode.el
(autoload 'dns-mode "dns-mode" "\
;;;***
\f
;;;### (autoloads (doc-view-bookmark-jump doc-view-minor-mode doc-view-mode-maybe
-;;;;;; doc-view-mode doc-view-mode-p) "doc-view" "doc-view.el" (20378
-;;;;;; 29222))
+;;;;;; doc-view-mode doc-view-mode-p) "doc-view" "doc-view.el" (20377
+;;;;;; 36640))
;;; Generated autoloads from doc-view.el
(autoload 'doc-view-mode-p "doc-view" "\
;;;***
\f
-;;;### (autoloads (doctor) "doctor" "play/doctor.el" (20355 10021))
+;;;### (autoloads (doctor) "doctor" "play/doctor.el" (20446 34252))
;;; Generated autoloads from play/doctor.el
(autoload 'doctor "doctor" "\
;;;***
\f
-;;;### (autoloads (double-mode) "double" "double.el" (20355 10021))
+;;;### (autoloads (double-mode) "double" "double.el" (20244 35516))
;;; Generated autoloads from double.el
(autoload 'double-mode "double" "\
;;;***
\f
-;;;### (autoloads (dunnet) "dunnet" "play/dunnet.el" (20355 10021))
+;;;### (autoloads (dunnet) "dunnet" "play/dunnet.el" (20244 35516))
;;; Generated autoloads from play/dunnet.el
(autoload 'dunnet "dunnet" "\
\f
;;;### (autoloads (easy-mmode-defsyntax easy-mmode-defmap easy-mmode-define-keymap
;;;;;; define-globalized-minor-mode define-minor-mode) "easy-mmode"
-;;;;;; "emacs-lisp/easy-mmode.el" (20423 17700))
+;;;;;; "emacs-lisp/easy-mmode.el" (20438 17064))
;;; Generated autoloads from emacs-lisp/easy-mmode.el
(defalias 'easy-mmode-define-minor-mode 'define-minor-mode)
function adds a basic doc-string stating these facts.
Optional INIT-VALUE is the initial value of the mode's variable.
-Optional LIGHTER is displayed in the modeline when the mode is on.
+Optional LIGHTER is displayed in the mode line when the mode is on.
Optional KEYMAP is the default keymap bound to the mode keymap.
If non-nil, it should be a variable name (whose value is a keymap),
or an expression that returns either a keymap or a list of
;;;***
\f
;;;### (autoloads (easy-menu-change easy-menu-create-menu easy-menu-do-define
-;;;;;; easy-menu-define) "easymenu" "emacs-lisp/easymenu.el" (20355
-;;;;;; 10021))
+;;;;;; easy-menu-define) "easymenu" "emacs-lisp/easymenu.el" (20438
+;;;;;; 17064))
;;; Generated autoloads from emacs-lisp/easymenu.el
(autoload 'easy-menu-define "easymenu" "\
A menu item can be a list with the same format as MENU. This is a submenu.
-\(fn SYMBOL MAPS DOC MENU)" nil (quote macro))
+\(fn SYMBOL MAPS DOC MENU)" nil t)
(put 'easy-menu-define 'lisp-indent-function 'defun)
;;;;;; ebnf-eps-file ebnf-eps-directory ebnf-spool-region ebnf-spool-buffer
;;;;;; ebnf-spool-file ebnf-spool-directory ebnf-print-region ebnf-print-buffer
;;;;;; ebnf-print-file ebnf-print-directory ebnf-customize) "ebnf2ps"
-;;;;;; "progmodes/ebnf2ps.el" (20373 11301))
+;;;;;; "progmodes/ebnf2ps.el" (20373 41604))
;;; Generated autoloads from progmodes/ebnf2ps.el
(autoload 'ebnf-customize "ebnf2ps" "\
;;;;;; ebrowse-electric-position-menu ebrowse-forward-in-position-stack
;;;;;; ebrowse-back-in-position-stack ebrowse-tags-search-member-use
;;;;;; ebrowse-tags-query-replace ebrowse-tags-search ebrowse-tags-loop-continue
-;;;;;; ebrowse-tags-complete-symbol ebrowse-tags-find-definition-other-frame
-;;;;;; ebrowse-tags-view-definition-other-frame ebrowse-tags-find-declaration-other-frame
-;;;;;; ebrowse-tags-find-definition-other-window ebrowse-tags-view-definition-other-window
-;;;;;; ebrowse-tags-find-declaration-other-window ebrowse-tags-find-definition
-;;;;;; ebrowse-tags-view-definition ebrowse-tags-find-declaration
-;;;;;; ebrowse-tags-view-declaration ebrowse-member-mode ebrowse-electric-choose-tree
-;;;;;; ebrowse-tree-mode) "ebrowse" "progmodes/ebrowse.el" (20355
-;;;;;; 10021))
+;;;;;; ebrowse-tags-find-definition-other-frame ebrowse-tags-view-definition-other-frame
+;;;;;; ebrowse-tags-find-declaration-other-frame ebrowse-tags-find-definition-other-window
+;;;;;; ebrowse-tags-view-definition-other-window ebrowse-tags-find-declaration-other-window
+;;;;;; ebrowse-tags-find-definition ebrowse-tags-view-definition
+;;;;;; ebrowse-tags-find-declaration ebrowse-tags-view-declaration
+;;;;;; ebrowse-member-mode ebrowse-electric-choose-tree ebrowse-tree-mode)
+;;;;;; "ebrowse" "progmodes/ebrowse.el" (20434 28080))
;;; Generated autoloads from progmodes/ebrowse.el
(autoload 'ebrowse-tree-mode "ebrowse" "\
\(fn)" t nil)
-(autoload 'ebrowse-tags-complete-symbol "ebrowse" "\
-Perform completion on the C++ symbol preceding point.
-A second call of this function without changing point inserts the next match.
-A call with prefix PREFIX reads the symbol to insert from the minibuffer with
-completion.
-
-\(fn PREFIX)" t nil)
-
(autoload 'ebrowse-tags-loop-continue "ebrowse" "\
Repeat last operation on files in tree.
FIRST-TIME non-nil means this is not a repetition, but the first time.
;;;***
\f
;;;### (autoloads (electric-buffer-list) "ebuff-menu" "ebuff-menu.el"
-;;;;;; (20400 56227))
+;;;;;; (20438 17064))
;;; Generated autoloads from ebuff-menu.el
(autoload 'electric-buffer-list "ebuff-menu" "\
;;;***
\f
;;;### (autoloads (Electric-command-history-redo-expression) "echistory"
-;;;;;; "echistory.el" (20355 10021))
+;;;;;; "echistory.el" (20244 35516))
;;; Generated autoloads from echistory.el
(autoload 'Electric-command-history-redo-expression "echistory" "\
;;;***
\f
;;;### (autoloads (ecomplete-setup) "ecomplete" "gnus/ecomplete.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/ecomplete.el
(autoload 'ecomplete-setup "ecomplete" "\
;;;***
\f
-;;;### (autoloads (global-ede-mode) "ede" "cedet/ede.el" (20355 10021))
+;;;### (autoloads (global-ede-mode) "ede" "cedet/ede.el" (20244 35516))
;;; Generated autoloads from cedet/ede.el
(defvar global-ede-mode nil "\
\f
;;;### (autoloads (edebug-all-forms edebug-all-defs edebug-eval-top-level-form
;;;;;; edebug-basic-spec edebug-all-forms edebug-all-defs) "edebug"
-;;;;;; "emacs-lisp/edebug.el" (20417 65331))
+;;;;;; "emacs-lisp/edebug.el" (20446 34252))
;;; Generated autoloads from emacs-lisp/edebug.el
(defvar edebug-all-defs nil "\
;;;;;; ediff-merge-directories-with-ancestor ediff-merge-directories
;;;;;; ediff-directories3 ediff-directory-revisions ediff-directories
;;;;;; ediff-buffers3 ediff-buffers ediff-backup ediff-current-file
-;;;;;; ediff-files3 ediff-files) "ediff" "vc/ediff.el" (20373 11301))
+;;;;;; ediff-files3 ediff-files) "ediff" "vc/ediff.el" (20373 41604))
;;; Generated autoloads from vc/ediff.el
(autoload 'ediff-files "ediff" "\
;;;***
\f
;;;### (autoloads (ediff-customize) "ediff-help" "vc/ediff-help.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from vc/ediff-help.el
(autoload 'ediff-customize "ediff-help" "\
;;;***
\f
;;;### (autoloads (ediff-show-registry) "ediff-mult" "vc/ediff-mult.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from vc/ediff-mult.el
(autoload 'ediff-show-registry "ediff-mult" "\
;;;***
\f
;;;### (autoloads (ediff-toggle-use-toolbar ediff-toggle-multiframe)
-;;;;;; "ediff-util" "vc/ediff-util.el" (20355 10021))
+;;;;;; "ediff-util" "vc/ediff-util.el" (20318 5885))
;;; Generated autoloads from vc/ediff-util.el
(autoload 'ediff-toggle-multiframe "ediff-util" "\
\f
;;;### (autoloads (format-kbd-macro read-kbd-macro edit-named-kbd-macro
;;;;;; edit-last-kbd-macro edit-kbd-macro) "edmacro" "edmacro.el"
-;;;;;; (20355 10021))
+;;;;;; (20438 17064))
;;; Generated autoloads from edmacro.el
(autoload 'edit-kbd-macro "edmacro" "\
;;;***
\f
;;;### (autoloads (edt-emulation-on edt-set-scroll-margins) "edt"
-;;;;;; "emulation/edt.el" (20355 10021))
+;;;;;; "emulation/edt.el" (20448 36271))
;;; Generated autoloads from emulation/edt.el
(autoload 'edt-set-scroll-margins "edt" "\
;;;***
\f
;;;### (autoloads (electric-helpify with-electric-help) "ehelp" "ehelp.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from ehelp.el
(autoload 'with-electric-help "ehelp" "\
;;;***
\f
;;;### (autoloads (turn-on-eldoc-mode eldoc-mode eldoc-minor-mode-string)
-;;;;;; "eldoc" "emacs-lisp/eldoc.el" (20355 10021))
+;;;;;; "eldoc" "emacs-lisp/eldoc.el" (20244 35516))
;;; Generated autoloads from emacs-lisp/eldoc.el
(defvar eldoc-minor-mode-string (purecopy " ElDoc") "\
;;;***
\f
;;;### (autoloads (electric-layout-mode electric-pair-mode electric-indent-mode)
-;;;;;; "electric" "electric.el" (20369 14251))
+;;;;;; "electric" "electric.el" (20373 41604))
;;; Generated autoloads from electric.el
(defvar electric-indent-chars '(10) "\
;;;***
\f
-;;;### (autoloads (elide-head) "elide-head" "elide-head.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (elide-head) "elide-head" "elide-head.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from elide-head.el
(autoload 'elide-head "elide-head" "\
\f
;;;### (autoloads (elint-initialize elint-defun elint-current-buffer
;;;;;; elint-directory elint-file) "elint" "emacs-lisp/elint.el"
-;;;;;; (20421 62373))
+;;;;;; (20423 37562))
;;; Generated autoloads from emacs-lisp/elint.el
(autoload 'elint-file "elint" "\
;;;***
\f
;;;### (autoloads (elp-results elp-instrument-package elp-instrument-list
-;;;;;; elp-instrument-function) "elp" "emacs-lisp/elp.el" (20355
-;;;;;; 10021))
+;;;;;; elp-instrument-function) "elp" "emacs-lisp/elp.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from emacs-lisp/elp.el
(autoload 'elp-instrument-function "elp" "\
;;;***
\f
;;;### (autoloads (emacs-lock-mode) "emacs-lock" "emacs-lock.el"
-;;;;;; (20399 35365))
+;;;;;; (20412 11425))
;;; Generated autoloads from emacs-lock.el
(autoload 'emacs-lock-mode "emacs-lock" "\
;;;***
\f
;;;### (autoloads (report-emacs-bug-query-existing-bugs report-emacs-bug)
-;;;;;; "emacsbug" "mail/emacsbug.el" (20411 26532))
+;;;;;; "emacsbug" "mail/emacsbug.el" (20432 42254))
;;; Generated autoloads from mail/emacsbug.el
(autoload 'report-emacs-bug "emacsbug" "\
;;;;;; emerge-revisions emerge-files-with-ancestor-remote emerge-files-remote
;;;;;; emerge-files-with-ancestor-command emerge-files-command emerge-buffers-with-ancestor
;;;;;; emerge-buffers emerge-files-with-ancestor emerge-files) "emerge"
-;;;;;; "vc/emerge.el" (20355 10021))
+;;;;;; "vc/emerge.el" (20356 35090))
;;; Generated autoloads from vc/emerge.el
(autoload 'emerge-files "emerge" "\
;;;***
\f
;;;### (autoloads (enriched-decode enriched-encode enriched-mode)
-;;;;;; "enriched" "textmodes/enriched.el" (20355 10021))
+;;;;;; "enriched" "textmodes/enriched.el" (20276 3849))
;;; Generated autoloads from textmodes/enriched.el
(autoload 'enriched-mode "enriched" "\
;;;;;; epa-sign-region epa-verify-cleartext-in-region epa-verify-region
;;;;;; epa-decrypt-armor-in-region epa-decrypt-region epa-encrypt-file
;;;;;; epa-sign-file epa-verify-file epa-decrypt-file epa-select-keys
-;;;;;; epa-list-secret-keys epa-list-keys) "epa" "epa.el" (20355
-;;;;;; 10021))
+;;;;;; epa-list-secret-keys epa-list-keys) "epa" "epa.el" (20434
+;;;;;; 28080))
;;; Generated autoloads from epa.el
(autoload 'epa-list-keys "epa" "\
;;;***
\f
;;;### (autoloads (epa-dired-do-encrypt epa-dired-do-sign epa-dired-do-verify
-;;;;;; epa-dired-do-decrypt) "epa-dired" "epa-dired.el" (20355 10021))
+;;;;;; epa-dired-do-decrypt) "epa-dired" "epa-dired.el" (20244 35516))
;;; Generated autoloads from epa-dired.el
(autoload 'epa-dired-do-decrypt "epa-dired" "\
;;;***
\f
;;;### (autoloads (epa-file-disable epa-file-enable epa-file-handler)
-;;;;;; "epa-file" "epa-file.el" (20355 10021))
+;;;;;; "epa-file" "epa-file.el" (20244 35516))
;;; Generated autoloads from epa-file.el
(autoload 'epa-file-handler "epa-file" "\
\f
;;;### (autoloads (epa-global-mail-mode epa-mail-import-keys epa-mail-encrypt
;;;;;; epa-mail-sign epa-mail-verify epa-mail-decrypt epa-mail-mode)
-;;;;;; "epa-mail" "epa-mail.el" (20355 10021))
+;;;;;; "epa-mail" "epa-mail.el" (20318 5885))
;;; Generated autoloads from epa-mail.el
(autoload 'epa-mail-mode "epa-mail" "\
;;;***
\f
-;;;### (autoloads (epg-make-context) "epg" "epg.el" (20355 10021))
+;;;### (autoloads (epg-make-context) "epg" "epg.el" (20244 35516))
;;; Generated autoloads from epg.el
(autoload 'epg-make-context "epg" "\
;;;***
\f
;;;### (autoloads (epg-expand-group epg-check-configuration epg-configuration)
-;;;;;; "epg-config" "epg-config.el" (20373 11301))
+;;;;;; "epg-config" "epg-config.el" (20373 41604))
;;; Generated autoloads from epg-config.el
(autoload 'epg-configuration "epg-config" "\
;;;***
\f
-;;;### (autoloads (erc-handle-irc-url erc-tls erc erc-select-read-args)
-;;;;;; "erc" "erc/erc.el" (20356 2211))
+;;;### (autoloads (erc-handle-irc-url erc-tls erc-select-read-args)
+;;;;;; "erc" "erc/erc.el" (20446 34252))
;;; Generated autoloads from erc/erc.el
(autoload 'erc-select-read-args "erc" "\
\(fn)" nil nil)
-(autoload 'erc "erc" "\
-ERC is a powerful, modular, and extensible IRC client.
-This function is the main entry point for ERC.
-
-It permits you to select connection parameters, and then starts ERC.
-
-Non-interactively, it takes the keyword arguments
- (server (erc-compute-server))
- (port (erc-compute-port))
- (nick (erc-compute-nick))
- password
- (full-name (erc-compute-full-name)))
-
-That is, if called with
-
- (erc :server \"irc.freenode.net\" :full-name \"Harry S Truman\")
-
-then the server and full-name will be set to those values, whereas
-`erc-compute-port', `erc-compute-nick' and `erc-compute-full-name' will
-be invoked for the values of the other parameters.
-
-\(fn &key (server (erc-compute-server)) (port (erc-compute-port)) (nick (erc-compute-nick)) PASSWORD (full-name (erc-compute-full-name)))" t nil)
-
(defalias 'erc-select 'erc)
(autoload 'erc-tls "erc" "\
;;;***
\f
-;;;### (autoloads nil "erc-autoaway" "erc/erc-autoaway.el" (20355
-;;;;;; 10021))
+;;;### (autoloads nil "erc-autoaway" "erc/erc-autoaway.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from erc/erc-autoaway.el
(autoload 'erc-autoaway-mode "erc-autoaway")
;;;***
\f
-;;;### (autoloads nil "erc-button" "erc/erc-button.el" (20355 10021))
+;;;### (autoloads nil "erc-button" "erc/erc-button.el" (20434 28080))
;;; Generated autoloads from erc/erc-button.el
(autoload 'erc-button-mode "erc-button" nil t)
;;;***
\f
-;;;### (autoloads nil "erc-capab" "erc/erc-capab.el" (20355 10021))
+;;;### (autoloads nil "erc-capab" "erc/erc-capab.el" (20244 35516))
;;; Generated autoloads from erc/erc-capab.el
(autoload 'erc-capab-identify-mode "erc-capab" nil t)
;;;***
\f
-;;;### (autoloads nil "erc-compat" "erc/erc-compat.el" (20355 10021))
+;;;### (autoloads nil "erc-compat" "erc/erc-compat.el" (20318 5885))
;;; Generated autoloads from erc/erc-compat.el
(autoload 'erc-define-minor-mode "erc-compat")
;;;***
\f
;;;### (autoloads (erc-ctcp-query-DCC pcomplete/erc-mode/DCC erc-cmd-DCC)
-;;;;;; "erc-dcc" "erc/erc-dcc.el" (20402 11562))
+;;;;;; "erc-dcc" "erc/erc-dcc.el" (20446 34252))
;;; Generated autoloads from erc/erc-dcc.el
(autoload 'erc-dcc-mode "erc-dcc")
\(fn)" nil nil)
(defvar erc-ctcp-query-DCC-hook '(erc-ctcp-query-DCC) "\
-Hook variable for CTCP DCC queries")
+Hook variable for CTCP DCC queries.")
(autoload 'erc-ctcp-query-DCC "erc-dcc" "\
The function called when a CTCP DCC request is detected by the client.
;;;;;; erc-ezb-add-session erc-ezb-end-of-session-list erc-ezb-init-session-list
;;;;;; erc-ezb-identify erc-ezb-notice-autodetect erc-ezb-lookup-action
;;;;;; erc-ezb-get-login erc-cmd-ezb) "erc-ezbounce" "erc/erc-ezbounce.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from erc/erc-ezbounce.el
(autoload 'erc-cmd-ezb "erc-ezbounce" "\
;;;***
\f
-;;;### (autoloads (erc-fill) "erc-fill" "erc/erc-fill.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (erc-fill) "erc-fill" "erc/erc-fill.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from erc/erc-fill.el
(autoload 'erc-fill-mode "erc-fill" nil t)
;;;***
\f
;;;### (autoloads (erc-identd-stop erc-identd-start) "erc-identd"
-;;;;;; "erc/erc-identd.el" (20355 10021))
+;;;;;; "erc/erc-identd.el" (20244 35516))
;;; Generated autoloads from erc/erc-identd.el
(autoload 'erc-identd-mode "erc-identd")
;;;***
\f
;;;### (autoloads (erc-create-imenu-index) "erc-imenu" "erc/erc-imenu.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from erc/erc-imenu.el
(autoload 'erc-create-imenu-index "erc-imenu" "\
;;;***
\f
-;;;### (autoloads nil "erc-join" "erc/erc-join.el" (20356 2211))
+;;;### (autoloads nil "erc-join" "erc/erc-join.el" (20356 35090))
;;; Generated autoloads from erc/erc-join.el
(autoload 'erc-autojoin-mode "erc-join" nil t)
;;;***
\f
-;;;### (autoloads nil "erc-list" "erc/erc-list.el" (20355 10021))
+;;;### (autoloads nil "erc-list" "erc/erc-list.el" (20244 35516))
;;; Generated autoloads from erc/erc-list.el
(autoload 'erc-list-mode "erc-list")
;;;***
\f
;;;### (autoloads (erc-save-buffer-in-logs erc-logging-enabled) "erc-log"
-;;;;;; "erc/erc-log.el" (20355 10021))
+;;;;;; "erc/erc-log.el" (20356 35090))
;;; Generated autoloads from erc/erc-log.el
(autoload 'erc-log-mode "erc-log" nil t)
;;;### (autoloads (erc-delete-dangerous-host erc-add-dangerous-host
;;;;;; erc-delete-keyword erc-add-keyword erc-delete-fool erc-add-fool
;;;;;; erc-delete-pal erc-add-pal) "erc-match" "erc/erc-match.el"
-;;;;;; (20355 10021))
+;;;;;; (20434 28080))
;;; Generated autoloads from erc/erc-match.el
(autoload 'erc-match-mode "erc-match")
;;;***
\f
-;;;### (autoloads nil "erc-menu" "erc/erc-menu.el" (20355 10021))
+;;;### (autoloads nil "erc-menu" "erc/erc-menu.el" (20244 35516))
;;; Generated autoloads from erc/erc-menu.el
(autoload 'erc-menu-mode "erc-menu" nil t)
;;;***
\f
;;;### (autoloads (erc-cmd-WHOLEFT) "erc-netsplit" "erc/erc-netsplit.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from erc/erc-netsplit.el
(autoload 'erc-netsplit-mode "erc-netsplit")
;;;***
\f
;;;### (autoloads (erc-server-select erc-determine-network) "erc-networks"
-;;;;;; "erc/erc-networks.el" (20355 10021))
+;;;;;; "erc/erc-networks.el" (20244 35516))
;;; Generated autoloads from erc/erc-networks.el
(autoload 'erc-determine-network "erc-networks" "\
;;;***
\f
;;;### (autoloads (pcomplete/erc-mode/NOTIFY erc-cmd-NOTIFY) "erc-notify"
-;;;;;; "erc/erc-notify.el" (20355 10021))
+;;;;;; "erc/erc-notify.el" (20356 35090))
;;; Generated autoloads from erc/erc-notify.el
(autoload 'erc-notify-mode "erc-notify" nil t)
;;;***
\f
-;;;### (autoloads nil "erc-page" "erc/erc-page.el" (20355 10021))
+;;;### (autoloads nil "erc-page" "erc/erc-page.el" (20244 35516))
;;; Generated autoloads from erc/erc-page.el
(autoload 'erc-page-mode "erc-page")
;;;***
\f
-;;;### (autoloads nil "erc-pcomplete" "erc/erc-pcomplete.el" (20355
-;;;;;; 10021))
+;;;### (autoloads nil "erc-pcomplete" "erc/erc-pcomplete.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from erc/erc-pcomplete.el
(autoload 'erc-completion-mode "erc-pcomplete" nil t)
;;;***
\f
-;;;### (autoloads nil "erc-replace" "erc/erc-replace.el" (20355 10021))
+;;;### (autoloads nil "erc-replace" "erc/erc-replace.el" (20244 35516))
;;; Generated autoloads from erc/erc-replace.el
(autoload 'erc-replace-mode "erc-replace")
;;;***
\f
-;;;### (autoloads nil "erc-ring" "erc/erc-ring.el" (20355 10021))
+;;;### (autoloads nil "erc-ring" "erc/erc-ring.el" (20244 35516))
;;; Generated autoloads from erc/erc-ring.el
(autoload 'erc-ring-mode "erc-ring" nil t)
;;;***
\f
;;;### (autoloads (erc-nickserv-identify erc-nickserv-identify-mode)
-;;;;;; "erc-services" "erc/erc-services.el" (20357 58785))
+;;;;;; "erc-services" "erc/erc-services.el" (20359 18671))
;;; Generated autoloads from erc/erc-services.el
(autoload 'erc-services-mode "erc-services" nil t)
;;;***
\f
-;;;### (autoloads nil "erc-sound" "erc/erc-sound.el" (20355 10021))
+;;;### (autoloads nil "erc-sound" "erc/erc-sound.el" (20356 35090))
;;; Generated autoloads from erc/erc-sound.el
(autoload 'erc-sound-mode "erc-sound")
;;;***
\f
;;;### (autoloads (erc-speedbar-browser) "erc-speedbar" "erc/erc-speedbar.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from erc/erc-speedbar.el
(autoload 'erc-speedbar-browser "erc-speedbar" "\
;;;***
\f
-;;;### (autoloads nil "erc-spelling" "erc/erc-spelling.el" (20355
-;;;;;; 10021))
+;;;### (autoloads nil "erc-spelling" "erc/erc-spelling.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from erc/erc-spelling.el
(autoload 'erc-spelling-mode "erc-spelling" nil t)
;;;***
\f
-;;;### (autoloads nil "erc-stamp" "erc/erc-stamp.el" (20355 10021))
+;;;### (autoloads nil "erc-stamp" "erc/erc-stamp.el" (20434 28080))
;;; Generated autoloads from erc/erc-stamp.el
(autoload 'erc-timestamp-mode "erc-stamp" nil t)
;;;***
\f
;;;### (autoloads (erc-track-minor-mode) "erc-track" "erc/erc-track.el"
-;;;;;; (20355 10021))
+;;;;;; (20428 57510))
;;; Generated autoloads from erc/erc-track.el
(defvar erc-track-minor-mode nil "\
;;;***
\f
;;;### (autoloads (erc-truncate-buffer erc-truncate-buffer-to-size)
-;;;;;; "erc-truncate" "erc/erc-truncate.el" (20355 10021))
+;;;;;; "erc-truncate" "erc/erc-truncate.el" (20356 35090))
;;; Generated autoloads from erc/erc-truncate.el
(autoload 'erc-truncate-mode "erc-truncate" nil t)
;;;***
\f
;;;### (autoloads (erc-xdcc-add-file) "erc-xdcc" "erc/erc-xdcc.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from erc/erc-xdcc.el
(autoload 'erc-xdcc-mode "erc-xdcc")
;;;***
\f
;;;### (autoloads (ert-describe-test ert-run-tests-interactively
-;;;;;; ert-run-tests-batch-and-exit ert-run-tests-batch ert-deftest)
-;;;;;; "ert" "emacs-lisp/ert.el" (20355 10021))
+;;;;;; ert-run-tests-batch-and-exit ert-run-tests-batch) "ert" "emacs-lisp/ert.el"
+;;;;;; (20356 35090))
;;; Generated autoloads from emacs-lisp/ert.el
-(autoload 'ert-deftest "ert" "\
-Define NAME (a symbol) as a test.
-
-BODY is evaluated as a `progn' when the test is run. It should
-signal a condition on failure or just return if the test passes.
-
-`should', `should-not' and `should-error' are useful for
-assertions in BODY.
-
-Use `ert' to run tests interactively.
-
-Tests that are expected to fail can be marked as such
-using :expected-result. See `ert-test-result-type-p' for a
-description of valid values for RESULT-TYPE.
-
-\(fn NAME () [DOCSTRING] [:expected-result RESULT-TYPE] [:tags '(TAG...)] BODY...)" nil (quote macro))
-
-(put 'ert-deftest 'lisp-indent-function '2)
-
-(put 'ert-deftest 'doc-string-elt '3)
-
(put 'ert-deftest 'lisp-indent-function 2)
(put 'ert-info 'lisp-indent-function 1)
;;;***
\f
;;;### (autoloads (ert-kill-all-test-buffers) "ert-x" "emacs-lisp/ert-x.el"
-;;;;;; (20364 28960))
+;;;;;; (20373 41604))
;;; Generated autoloads from emacs-lisp/ert-x.el
(put 'ert-with-test-buffer 'lisp-indent-function 1)
;;;***
\f
-;;;### (autoloads (eshell-mode) "esh-mode" "eshell/esh-mode.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (eshell-mode) "esh-mode" "eshell/esh-mode.el" (20428
+;;;;;; 57510))
;;; Generated autoloads from eshell/esh-mode.el
(autoload 'eshell-mode "esh-mode" "\
;;;***
\f
;;;### (autoloads (eshell-command-result eshell-command eshell) "eshell"
-;;;;;; "eshell/eshell.el" (20373 11301))
+;;;;;; "eshell/eshell.el" (20373 41604))
;;; Generated autoloads from eshell/eshell.el
(autoload 'eshell "eshell" "\
;;;;;; visit-tags-table tags-table-mode find-tag-default-function
;;;;;; find-tag-hook tags-add-tables tags-compression-info-list
;;;;;; tags-table-list tags-case-fold-search) "etags" "progmodes/etags.el"
-;;;;;; (20388 65061))
+;;;;;; (20412 11425))
;;; Generated autoloads from progmodes/etags.el
(defvar tags-file-name nil "\
;;;;;; ethio-fidel-to-sera-marker ethio-fidel-to-sera-region ethio-fidel-to-sera-buffer
;;;;;; ethio-sera-to-fidel-marker ethio-sera-to-fidel-region ethio-sera-to-fidel-buffer
;;;;;; setup-ethiopic-environment-internal) "ethio-util" "language/ethio-util.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from language/ethio-util.el
(autoload 'setup-ethiopic-environment-internal "ethio-util" "\
\f
;;;### (autoloads (eudc-load-eudc eudc-query-form eudc-expand-inline
;;;;;; eudc-get-phone eudc-get-email eudc-set-server) "eudc" "net/eudc.el"
-;;;;;; (20355 10021))
+;;;;;; (20428 57510))
;;; Generated autoloads from net/eudc.el
(autoload 'eudc-set-server "eudc" "\
\f
;;;### (autoloads (eudc-display-jpeg-as-button eudc-display-jpeg-inline
;;;;;; eudc-display-sound eudc-display-mail eudc-display-url eudc-display-generic-binary)
-;;;;;; "eudc-bob" "net/eudc-bob.el" (20355 10021))
+;;;;;; "eudc-bob" "net/eudc-bob.el" (20244 35516))
;;; Generated autoloads from net/eudc-bob.el
(autoload 'eudc-display-generic-binary "eudc-bob" "\
;;;***
\f
;;;### (autoloads (eudc-try-bbdb-insert eudc-insert-record-at-point-into-bbdb)
-;;;;;; "eudc-export" "net/eudc-export.el" (20355 10021))
+;;;;;; "eudc-export" "net/eudc-export.el" (20244 35516))
;;; Generated autoloads from net/eudc-export.el
(autoload 'eudc-insert-record-at-point-into-bbdb "eudc-export" "\
;;;***
\f
;;;### (autoloads (eudc-edit-hotlist) "eudc-hotlist" "net/eudc-hotlist.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from net/eudc-hotlist.el
(autoload 'eudc-edit-hotlist "eudc-hotlist" "\
;;;***
\f
-;;;### (autoloads (ewoc-create) "ewoc" "emacs-lisp/ewoc.el" (20378
-;;;;;; 29222))
+;;;### (autoloads (ewoc-create) "ewoc" "emacs-lisp/ewoc.el" (20451
+;;;;;; 21087))
;;; Generated autoloads from emacs-lisp/ewoc.el
(autoload 'ewoc-create "ewoc" "\
;;;### (autoloads (executable-make-buffer-file-executable-if-script-p
;;;;;; executable-self-display executable-set-magic executable-interpret
;;;;;; executable-command-find-posix-p) "executable" "progmodes/executable.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from progmodes/executable.el
(autoload 'executable-command-find-posix-p "executable" "\
\f
;;;### (autoloads (expand-jump-to-next-slot expand-jump-to-previous-slot
;;;;;; expand-abbrev-hook expand-add-abbrevs) "expand" "expand.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from expand.el
(autoload 'expand-add-abbrevs "expand" "\
;;;***
\f
-;;;### (autoloads (f90-mode) "f90" "progmodes/f90.el" (20388 65061))
+;;;### (autoloads (f90-mode) "f90" "progmodes/f90.el" (20412 11425))
;;; Generated autoloads from progmodes/f90.el
(autoload 'f90-mode "f90" "\
;;;### (autoloads (variable-pitch-mode buffer-face-toggle buffer-face-set
;;;;;; buffer-face-mode text-scale-adjust text-scale-decrease text-scale-increase
;;;;;; text-scale-set face-remap-set-base face-remap-reset-base
-;;;;;; face-remap-add-relative) "face-remap" "face-remap.el" (20388
-;;;;;; 65061))
+;;;;;; face-remap-add-relative) "face-remap" "face-remap.el" (20446
+;;;;;; 34252))
;;; Generated autoloads from face-remap.el
(autoload 'face-remap-add-relative "face-remap" "\
Return a cookie which can be used to delete this remapping with
`face-remap-remove-relative'.
-The remaining arguments, SPECS, should be either a list of face
-names, or a property list of face attribute/value pairs. The
-remapping specified by SPECS takes effect alongside the
-remappings from other calls to `face-remap-add-relative', as well
-as the normal definition of FACE (at lowest priority). This
-function tries to sort multiple remappings for the same face, so
-that remappings specifying relative face attributes are applied
-after remappings specifying absolute face attributes.
+The remaining arguments, SPECS, should form a list of faces.
+Each list element should be either a face name or a property list
+of face attribute/value pairs. If more than one face is listed,
+that specifies an aggregate face, in the same way as in a `face'
+text property, except for possible priority changes noted below.
+
+The face remapping specified by SPECS takes effect alongside the
+remappings from other calls to `face-remap-add-relative' for the
+same FACE, as well as the normal definition of FACE (at lowest
+priority). This function tries to sort multiple remappings for
+the same face, so that remappings specifying relative face
+attributes are applied after remappings specifying absolute face
+attributes.
The base (lowest priority) remapping may be set to something
other than the normal definition of FACE via `face-remap-set-base'.
(autoload 'face-remap-set-base "face-remap" "\
Set the base remapping of FACE in the current buffer to SPECS.
This causes the remappings specified by `face-remap-add-relative'
-to apply on top of the face specification given by SPECS. SPECS
-should be either a list of face names, or a property list of face
-attribute/value pairs.
+to apply on top of the face specification given by SPECS.
+
+The remaining arguments, SPECS, should form a list of faces.
+Each list element should be either a face name or a property list
+of face attribute/value pairs, like in a `face' text property.
If SPECS is empty, call `face-remap-reset-base' to use the normal
definition of FACE as the base remapping; note that this is
(autoload 'buffer-face-set "face-remap" "\
Enable `buffer-face-mode', using face specs SPECS.
-SPECS can be any value suitable for the `face' text property,
-including a face name, a list of face names, or a face-attribute
-If SPECS is nil, then `buffer-face-mode' is disabled.
+Each argument in SPECS should be a face, i.e. either a face name
+or a property list of face attributes and values. If more than
+one face is listed, that specifies an aggregate face, like in a
+`face' text property. If SPECS is nil or omitted, disable
+`buffer-face-mode'.
-This function will make the variable `buffer-face-mode-face'
-buffer local, and set it to FACE.
+This function makes the variable `buffer-face-mode-face' buffer
+local, and sets it to FACE.
\(fn &rest SPECS)" t nil)
(autoload 'buffer-face-toggle "face-remap" "\
Toggle `buffer-face-mode', using face specs SPECS.
-SPECS can be any value suitable for the `face' text property,
-including a face name, a list of face names, or a face-attribute
+Each argument in SPECS should be a face, i.e. either a face name
+or a property list of face attributes and values. If more than
+one face is listed, that specifies an aggregate face, like in a
+`face' text property.
If `buffer-face-mode' is already enabled, and is currently using
the face specs SPECS, then it is disabled; if buffer-face-mode is
\f
;;;### (autoloads (feedmail-queue-reminder feedmail-run-the-queue
;;;;;; feedmail-run-the-queue-global-prompt feedmail-run-the-queue-no-prompts
-;;;;;; feedmail-send-it) "feedmail" "mail/feedmail.el" (20387 44199))
+;;;;;; feedmail-send-it) "feedmail" "mail/feedmail.el" (20412 11425))
;;; Generated autoloads from mail/feedmail.el
(autoload 'feedmail-send-it "feedmail" "\
\f
;;;### (autoloads (ffap-bindings ffap-guess-file-name-at-point dired-at-point
;;;;;; ffap-at-mouse ffap-menu find-file-at-point ffap-next) "ffap"
-;;;;;; "ffap.el" (20395 38306))
+;;;;;; "ffap.el" (20412 11425))
;;; Generated autoloads from ffap.el
(autoload 'ffap-next "ffap" "\
;;;### (autoloads (file-cache-minibuffer-complete file-cache-add-directory-recursively
;;;;;; file-cache-add-directory-using-locate file-cache-add-directory-using-find
;;;;;; file-cache-add-file file-cache-add-directory-list file-cache-add-directory)
-;;;;;; "filecache" "filecache.el" (20355 10021))
+;;;;;; "filecache" "filecache.el" (20244 35516))
;;; Generated autoloads from filecache.el
(autoload 'file-cache-add-directory "filecache" "\
;;;;;; copy-file-locals-to-dir-locals delete-dir-local-variable
;;;;;; add-dir-local-variable delete-file-local-variable-prop-line
;;;;;; add-file-local-variable-prop-line delete-file-local-variable
-;;;;;; add-file-local-variable) "files-x" "files-x.el" (20355 10021))
+;;;;;; add-file-local-variable) "files-x" "files-x.el" (20356 35090))
;;; Generated autoloads from files-x.el
(autoload 'add-file-local-variable "files-x" "\
;;;***
\f
-;;;### (autoloads (filesets-init) "filesets" "filesets.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (filesets-init) "filesets" "filesets.el" (20318
+;;;;;; 5885))
;;; Generated autoloads from filesets.el
(autoload 'filesets-init "filesets" "\
;;;***
\f
-;;;### (autoloads (find-cmd) "find-cmd" "find-cmd.el" (20355 10021))
+;;;### (autoloads (find-cmd) "find-cmd" "find-cmd.el" (20244 35516))
;;; Generated autoloads from find-cmd.el
(autoload 'find-cmd "find-cmd" "\
;;;***
\f
;;;### (autoloads (find-grep-dired find-name-dired find-dired) "find-dired"
-;;;;;; "find-dired.el" (20355 10021))
+;;;;;; "find-dired.el" (20244 35516))
;;; Generated autoloads from find-dired.el
(autoload 'find-dired "find-dired" "\
\f
;;;### (autoloads (ff-mouse-find-other-file-other-window ff-mouse-find-other-file
;;;;;; ff-find-other-file ff-get-other-file ff-special-constructs)
-;;;;;; "find-file" "find-file.el" (20387 44199))
+;;;;;; "find-file" "find-file.el" (20412 11425))
;;; Generated autoloads from find-file.el
(defvar ff-special-constructs `((,(purecopy "^#\\s *\\(include\\|import\\)\\s +[<\"]\\(.*\\)[>\"]") lambda nil (buffer-substring (match-beginning 2) (match-end 2)))) "\
;;;;;; find-variable find-variable-noselect find-function-other-frame
;;;;;; find-function-other-window find-function find-function-noselect
;;;;;; find-function-search-for-symbol find-library) "find-func"
-;;;;;; "emacs-lisp/find-func.el" (20355 10021))
+;;;;;; "emacs-lisp/find-func.el" (20244 35516))
;;; Generated autoloads from emacs-lisp/find-func.el
(autoload 'find-library "find-func" "\
;;;***
\f
;;;### (autoloads (find-lisp-find-dired-filter find-lisp-find-dired-subdirectories
-;;;;;; find-lisp-find-dired) "find-lisp" "find-lisp.el" (20355 10021))
+;;;;;; find-lisp-find-dired) "find-lisp" "find-lisp.el" (20244 35516))
;;; Generated autoloads from find-lisp.el
(autoload 'find-lisp-find-dired "find-lisp" "\
;;;***
\f
;;;### (autoloads (finder-by-keyword finder-commentary finder-list-keywords)
-;;;;;; "finder" "finder.el" (20355 10021))
+;;;;;; "finder" "finder.el" (20244 35516))
;;; Generated autoloads from finder.el
(autoload 'finder-list-keywords "finder" "\
;;;***
\f
;;;### (autoloads (enable-flow-control-on enable-flow-control) "flow-ctrl"
-;;;;;; "flow-ctrl.el" (20355 10021))
+;;;;;; "flow-ctrl.el" (20244 35516))
;;; Generated autoloads from flow-ctrl.el
(autoload 'enable-flow-control "flow-ctrl" "\
;;;***
\f
;;;### (autoloads (fill-flowed fill-flowed-encode) "flow-fill" "gnus/flow-fill.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/flow-fill.el
(autoload 'fill-flowed-encode "flow-fill" "\
;;;***
\f
;;;### (autoloads (flymake-find-file-hook flymake-mode-off flymake-mode-on
-;;;;;; flymake-mode) "flymake" "progmodes/flymake.el" (20373 11301))
+;;;;;; flymake-mode) "flymake" "progmodes/flymake.el" (20434 28080))
;;; Generated autoloads from progmodes/flymake.el
(autoload 'flymake-mode "flymake" "\
\f
;;;### (autoloads (flyspell-buffer flyspell-region flyspell-mode-off
;;;;;; turn-off-flyspell turn-on-flyspell flyspell-mode flyspell-prog-mode)
-;;;;;; "flyspell" "textmodes/flyspell.el" (20420 41510))
+;;;;;; "flyspell" "textmodes/flyspell.el" (20434 28080))
;;; Generated autoloads from textmodes/flyspell.el
(autoload 'flyspell-prog-mode "flyspell" "\
\f
;;;### (autoloads (follow-delete-other-windows-and-split follow-mode
;;;;;; turn-off-follow-mode turn-on-follow-mode) "follow" "follow.el"
-;;;;;; (20387 44199))
+;;;;;; (20412 11425))
;;; Generated autoloads from follow.el
(autoload 'turn-on-follow-mode "follow" "\
;;;***
\f
-;;;### (autoloads (footnote-mode) "footnote" "mail/footnote.el" (20387
-;;;;;; 44199))
+;;;### (autoloads (footnote-mode) "footnote" "mail/footnote.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from mail/footnote.el
(autoload 'footnote-mode "footnote" "\
;;;***
\f
;;;### (autoloads (forms-find-file-other-window forms-find-file forms-mode)
-;;;;;; "forms" "forms.el" (20392 20740))
+;;;;;; "forms" "forms.el" (20428 57510))
;;; Generated autoloads from forms.el
(autoload 'forms-mode "forms" "\
;;;***
\f
;;;### (autoloads (fortran-mode) "fortran" "progmodes/fortran.el"
-;;;;;; (20355 10021))
+;;;;;; (20446 34252))
;;; Generated autoloads from progmodes/fortran.el
(autoload 'fortran-mode "fortran" "\
;;;***
\f
;;;### (autoloads (fortune fortune-to-signature fortune-compile fortune-from-region
-;;;;;; fortune-add-fortune) "fortune" "play/fortune.el" (20355 10021))
+;;;;;; fortune-add-fortune) "fortune" "play/fortune.el" (20244 35516))
;;; Generated autoloads from play/fortune.el
(autoload 'fortune-add-fortune "fortune" "\
;;;***
\f
;;;### (autoloads (gdb gdb-enable-debug) "gdb-mi" "progmodes/gdb-mi.el"
-;;;;;; (20415 53309))
+;;;;;; (20415 57974))
;;; Generated autoloads from progmodes/gdb-mi.el
(defvar gdb-enable-debug nil "\
;;;***
\f
;;;### (autoloads (generic-make-keywords-list generic-mode generic-mode-internal
-;;;;;; define-generic-mode) "generic" "emacs-lisp/generic.el" (20406
-;;;;;; 8611))
+;;;;;; define-generic-mode) "generic" "emacs-lisp/generic.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from emacs-lisp/generic.el
(defvar generic-mode-list nil "\
See the file generic-x.el for some examples of `define-generic-mode'.
-\(fn MODE COMMENT-LIST KEYWORD-LIST FONT-LOCK-LIST AUTO-MODE-LIST FUNCTION-LIST &optional DOCSTRING)" nil (quote macro))
-
-(put 'define-generic-mode 'doc-string-elt '7)
+\(fn MODE COMMENT-LIST KEYWORD-LIST FONT-LOCK-LIST AUTO-MODE-LIST FUNCTION-LIST &optional DOCSTRING)" nil t)
(put 'define-generic-mode 'lisp-indent-function '1)
+(put 'define-generic-mode 'doc-string-elt '7)
+
(autoload 'generic-mode-internal "generic" "\
Go into the generic mode MODE.
;;;***
\f
;;;### (autoloads (glasses-mode) "glasses" "progmodes/glasses.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from progmodes/glasses.el
(autoload 'glasses-mode "glasses" "\
\f
;;;### (autoloads (gmm-tool-bar-from-list gmm-widget-p gmm-error
;;;;;; gmm-message gmm-regexp-concat) "gmm-utils" "gnus/gmm-utils.el"
-;;;;;; (20355 10021))
+;;;;;; (20318 5885))
;;; Generated autoloads from gnus/gmm-utils.el
(autoload 'gmm-regexp-concat "gmm-utils" "\
;;;***
\f
;;;### (autoloads (gnus gnus-other-frame gnus-slave gnus-no-server
-;;;;;; gnus-slave-no-server) "gnus" "gnus/gnus.el" (20414 2727))
+;;;;;; gnus-slave-no-server) "gnus" "gnus/gnus.el" (20414 21581))
;;; Generated autoloads from gnus/gnus.el
(when (fboundp 'custom-autoload)
(custom-autoload 'gnus-select-method "gnus"))
;;;;;; gnus-agent-get-undownloaded-list gnus-agent-delete-group
;;;;;; gnus-agent-rename-group gnus-agent-possibly-save-gcc gnus-agentize
;;;;;; gnus-slave-unplugged gnus-plugged gnus-unplugged) "gnus-agent"
-;;;;;; "gnus/gnus-agent.el" (20355 10021))
+;;;;;; "gnus/gnus-agent.el" (20446 34252))
;;; Generated autoloads from gnus/gnus-agent.el
(autoload 'gnus-unplugged "gnus-agent" "\
;;;***
\f
;;;### (autoloads (gnus-article-prepare-display) "gnus-art" "gnus/gnus-art.el"
-;;;;;; (20361 20134))
+;;;;;; (20373 41604))
;;; Generated autoloads from gnus/gnus-art.el
(autoload 'gnus-article-prepare-display "gnus-art" "\
;;;***
\f
;;;### (autoloads (gnus-bookmark-bmenu-list gnus-bookmark-jump gnus-bookmark-set)
-;;;;;; "gnus-bookmark" "gnus/gnus-bookmark.el" (20355 10021))
+;;;;;; "gnus-bookmark" "gnus/gnus-bookmark.el" (20244 35516))
;;; Generated autoloads from gnus/gnus-bookmark.el
(autoload 'gnus-bookmark-set "gnus-bookmark" "\
\f
;;;### (autoloads (gnus-cache-delete-group gnus-cache-rename-group
;;;;;; gnus-cache-generate-nov-databases gnus-cache-generate-active
-;;;;;; gnus-jog-cache) "gnus-cache" "gnus/gnus-cache.el" (20355
-;;;;;; 10021))
+;;;;;; gnus-jog-cache) "gnus-cache" "gnus/gnus-cache.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from gnus/gnus-cache.el
(autoload 'gnus-jog-cache "gnus-cache" "\
;;;***
\f
;;;### (autoloads (gnus-delay-initialize gnus-delay-send-queue gnus-delay-article)
-;;;;;; "gnus-delay" "gnus/gnus-delay.el" (20355 10021))
+;;;;;; "gnus-delay" "gnus/gnus-delay.el" (20244 35516))
;;; Generated autoloads from gnus/gnus-delay.el
(autoload 'gnus-delay-article "gnus-delay" "\
;;;***
\f
;;;### (autoloads (gnus-user-format-function-D gnus-user-format-function-d)
-;;;;;; "gnus-diary" "gnus/gnus-diary.el" (20355 10021))
+;;;;;; "gnus-diary" "gnus/gnus-diary.el" (20244 35516))
;;; Generated autoloads from gnus/gnus-diary.el
(autoload 'gnus-user-format-function-d "gnus-diary" "\
;;;***
\f
;;;### (autoloads (turn-on-gnus-dired-mode) "gnus-dired" "gnus/gnus-dired.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/gnus-dired.el
(autoload 'turn-on-gnus-dired-mode "gnus-dired" "\
;;;***
\f
;;;### (autoloads (gnus-draft-reminder) "gnus-draft" "gnus/gnus-draft.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/gnus-draft.el
(autoload 'gnus-draft-reminder "gnus-draft" "\
\f
;;;### (autoloads (gnus-convert-png-to-face gnus-convert-face-to-png
;;;;;; gnus-face-from-file gnus-x-face-from-file gnus-insert-random-x-face-header
-;;;;;; gnus-random-x-face) "gnus-fun" "gnus/gnus-fun.el" (20355
-;;;;;; 10021))
+;;;;;; gnus-random-x-face) "gnus-fun" "gnus/gnus-fun.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from gnus/gnus-fun.el
(autoload 'gnus-random-x-face "gnus-fun" "\
;;;***
\f
;;;### (autoloads (gnus-treat-mail-gravatar gnus-treat-from-gravatar)
-;;;;;; "gnus-gravatar" "gnus/gnus-gravatar.el" (20355 10021))
+;;;;;; "gnus-gravatar" "gnus/gnus-gravatar.el" (20244 35516))
;;; Generated autoloads from gnus/gnus-gravatar.el
(autoload 'gnus-treat-from-gravatar "gnus-gravatar" "\
;;;***
\f
;;;### (autoloads (gnus-fetch-group-other-frame gnus-fetch-group)
-;;;;;; "gnus-group" "gnus/gnus-group.el" (20355 10021))
+;;;;;; "gnus-group" "gnus/gnus-group.el" (20438 17064))
;;; Generated autoloads from gnus/gnus-group.el
(autoload 'gnus-fetch-group "gnus-group" "\
;;;***
\f
;;;### (autoloads (gnus-html-prefetch-images gnus-article-html) "gnus-html"
-;;;;;; "gnus/gnus-html.el" (20355 10021))
+;;;;;; "gnus/gnus-html.el" (20276 3849))
;;; Generated autoloads from gnus/gnus-html.el
(autoload 'gnus-article-html "gnus-html" "\
;;;***
\f
;;;### (autoloads (gnus-batch-score) "gnus-kill" "gnus/gnus-kill.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/gnus-kill.el
(defalias 'gnus-batch-kill 'gnus-batch-score)
\f
;;;### (autoloads (gnus-mailing-list-mode gnus-mailing-list-insinuate
;;;;;; turn-on-gnus-mailing-list-mode) "gnus-ml" "gnus/gnus-ml.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/gnus-ml.el
(autoload 'turn-on-gnus-mailing-list-mode "gnus-ml" "\
\f
;;;### (autoloads (gnus-group-split-fancy gnus-group-split gnus-group-split-update
;;;;;; gnus-group-split-setup) "gnus-mlspl" "gnus/gnus-mlspl.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/gnus-mlspl.el
(autoload 'gnus-group-split-setup "gnus-mlspl" "\
;;;***
\f
;;;### (autoloads (gnus-button-reply gnus-button-mailto gnus-msg-mail)
-;;;;;; "gnus-msg" "gnus/gnus-msg.el" (20417 65331))
+;;;;;; "gnus-msg" "gnus/gnus-msg.el" (20434 28080))
;;; Generated autoloads from gnus/gnus-msg.el
(autoload 'gnus-msg-mail "gnus-msg" "\
\f
;;;### (autoloads (gnus-treat-newsgroups-picon gnus-treat-mail-picon
;;;;;; gnus-treat-from-picon) "gnus-picon" "gnus/gnus-picon.el"
-;;;;;; (20355 10021))
+;;;;;; (20290 33419))
;;; Generated autoloads from gnus/gnus-picon.el
(autoload 'gnus-treat-from-picon "gnus-picon" "\
;;;;;; gnus-sorted-nintersection gnus-sorted-range-intersection
;;;;;; gnus-sorted-intersection gnus-intersection gnus-sorted-complement
;;;;;; gnus-sorted-ndifference gnus-sorted-difference) "gnus-range"
-;;;;;; "gnus/gnus-range.el" (20355 10021))
+;;;;;; "gnus/gnus-range.el" (20244 35516))
;;; Generated autoloads from gnus/gnus-range.el
(autoload 'gnus-sorted-difference "gnus-range" "\
;;;***
\f
;;;### (autoloads (gnus-registry-install-hooks gnus-registry-initialize)
-;;;;;; "gnus-registry" "gnus/gnus-registry.el" (20415 53309))
+;;;;;; "gnus-registry" "gnus/gnus-registry.el" (20415 57974))
;;; Generated autoloads from gnus/gnus-registry.el
(autoload 'gnus-registry-initialize "gnus-registry" "\
;;;***
\f
;;;### (autoloads (gnus-sieve-article-add-rule gnus-sieve-generate
-;;;;;; gnus-sieve-update) "gnus-sieve" "gnus/gnus-sieve.el" (20355
-;;;;;; 10021))
+;;;;;; gnus-sieve-update) "gnus-sieve" "gnus/gnus-sieve.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from gnus/gnus-sieve.el
(autoload 'gnus-sieve-update "gnus-sieve" "\
;;;***
\f
;;;### (autoloads (gnus-update-format) "gnus-spec" "gnus/gnus-spec.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/gnus-spec.el
(autoload 'gnus-update-format "gnus-spec" "\
;;;***
\f
;;;### (autoloads (gnus-declare-backend) "gnus-start" "gnus/gnus-start.el"
-;;;;;; (20361 20134))
+;;;;;; (20373 41604))
;;; Generated autoloads from gnus/gnus-start.el
(autoload 'gnus-declare-backend "gnus-start" "\
;;;***
\f
;;;### (autoloads (gnus-summary-bookmark-jump) "gnus-sum" "gnus/gnus-sum.el"
-;;;;;; (20355 10021))
+;;;;;; (20331 12564))
;;; Generated autoloads from gnus/gnus-sum.el
(autoload 'gnus-summary-bookmark-jump "gnus-sum" "\
;;;***
\f
;;;### (autoloads (gnus-sync-install-hooks gnus-sync-initialize)
-;;;;;; "gnus-sync" "gnus/gnus-sync.el" (20355 10021))
+;;;;;; "gnus-sync" "gnus/gnus-sync.el" (20244 35516))
;;; Generated autoloads from gnus/gnus-sync.el
(autoload 'gnus-sync-initialize "gnus-sync" "\
;;;***
\f
;;;### (autoloads (gnus-add-configuration) "gnus-win" "gnus/gnus-win.el"
-;;;;;; (20420 41510))
+;;;;;; (20448 36271))
;;; Generated autoloads from gnus/gnus-win.el
(autoload 'gnus-add-configuration "gnus-win" "\
;;;***
\f
;;;### (autoloads (gnutls-min-prime-bits) "gnutls" "net/gnutls.el"
-;;;;;; (20417 65331))
+;;;;;; (20419 46656))
;;; Generated autoloads from net/gnutls.el
(defvar gnutls-min-prime-bits 256 "\
;;;***
\f
-;;;### (autoloads (gomoku) "gomoku" "play/gomoku.el" (20355 10021))
+;;;### (autoloads (gomoku) "gomoku" "play/gomoku.el" (20356 35090))
;;; Generated autoloads from play/gomoku.el
(autoload 'gomoku "gomoku" "\
;;;***
\f
;;;### (autoloads (goto-address-prog-mode goto-address-mode goto-address
-;;;;;; goto-address-at-point) "goto-addr" "net/goto-addr.el" (20355
-;;;;;; 10021))
+;;;;;; goto-address-at-point) "goto-addr" "net/goto-addr.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from net/goto-addr.el
(define-obsolete-function-alias 'goto-address-at-mouse 'goto-address-at-point "22.1")
;;;***
\f
;;;### (autoloads (gravatar-retrieve-synchronously gravatar-retrieve)
-;;;;;; "gravatar" "gnus/gravatar.el" (20355 10021))
+;;;;;; "gravatar" "gnus/gravatar.el" (20290 33419))
;;; Generated autoloads from gnus/gravatar.el
(autoload 'gravatar-retrieve "gravatar" "\
\f
;;;### (autoloads (zrgrep rgrep lgrep grep-find grep grep-mode grep-compute-defaults
;;;;;; grep-process-setup grep-setup-hook grep-find-command grep-command
-;;;;;; grep-window-height) "grep" "progmodes/grep.el" (20369 14251))
+;;;;;; grep-window-height) "grep" "progmodes/grep.el" (20373 41604))
;;; Generated autoloads from progmodes/grep.el
(defvar grep-window-height nil "\
;;;***
\f
-;;;### (autoloads (gs-load-image) "gs" "gs.el" (20355 10021))
+;;;### (autoloads (gs-load-image) "gs" "gs.el" (20244 35516))
;;; Generated autoloads from gs.el
(autoload 'gs-load-image "gs" "\
;;;***
\f
;;;### (autoloads (gud-tooltip-mode gdb-script-mode jdb pdb perldb
-;;;;;; xdb dbx sdb gud-gdb) "gud" "progmodes/gud.el" (20373 11301))
+;;;;;; xdb dbx sdb gud-gdb) "gud" "progmodes/gud.el" (20373 41604))
;;; Generated autoloads from progmodes/gud.el
(autoload 'gud-gdb "gud" "\
;;;***
\f
-;;;### (autoloads (handwrite) "handwrite" "play/handwrite.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (setf gv-define-simple-setter gv-define-setter
+;;;;;; gv-define-expander gv-letplace gv-get) "gv" "emacs-lisp/gv.el"
+;;;;;; (20451 34840))
+;;; Generated autoloads from emacs-lisp/gv.el
+
+(autoload 'gv-get "gv" "\
+Build the code that applies DO to PLACE.
+PLACE must be a valid generalized variable.
+DO must be a function; it will be called with 2 arguments: GETTER and SETTER,
+where GETTER is a (copyable) Elisp expression that returns the value of PLACE,
+and SETTER is a function which returns the code to set PLACE when called
+with a (not necessarily copyable) Elisp expression that returns the value to
+set it to.
+DO must return an Elisp expression.
+
+\(fn PLACE DO)" nil nil)
+
+(autoload 'gv-letplace "gv" "\
+Build the code manipulating the generalized variable PLACE.
+GETTER will be bound to a copyable expression that returns the value
+of PLACE.
+SETTER will be bound to a function that takes an expression V and returns
+and new expression that sets PLACE to V.
+BODY should return some Elisp expression E manipulating PLACE via GETTER
+and SETTER.
+The returned value will then be an Elisp expression that first evaluates
+all the parts of PLACE that can be evaluated and then runs E.
+
+\(fn (GETTER SETTER) PLACE &rest BODY)" nil t)
+
+(put 'gv-letplace 'lisp-indent-function '2)
+
+(autoload 'gv-define-expander "gv" "\
+Use HANDLER to handle NAME as a generalized var.
+NAME is a symbol: the name of a function, macro, or special form.
+HANDLER is a function which takes an argument DO followed by the same
+arguments as NAME. DO is a function as defined in `gv-get'.
+
+\(fn NAME HANDLER)" nil t)
+
+(put 'gv-define-expander 'lisp-indent-function '1)
+
+(autoload 'gv-define-setter "gv" "\
+Define a setter method for generalized variable NAME.
+This macro is an easy-to-use substitute for `gv-define-expander' that works
+well for simple place forms.
+Assignments of VAL to (NAME ARGS...) are expanded by binding the argument
+forms (VAL ARGS...) according to ARGLIST, then executing BODY, which must
+return a Lisp form that does the assignment.
+Actually, ARGLIST may be bound to temporary variables which are introduced
+automatically to preserve proper execution order of the arguments. Example:
+ (gv-define-setter aref (v a i) `(aset ,a ,i ,v))
+
+\(fn NAME ARGLIST &rest BODY)" nil t)
+
+(put 'gv-define-setter 'lisp-indent-function '2)
+
+(autoload 'gv-define-simple-setter "gv" "\
+Define a simple setter method for generalized variable NAME.
+This macro is an easy-to-use substitute for `gv-define-expander' that works
+well for simple place forms. Assignments of VAL to (NAME ARGS...) are
+turned into calls of the form (SETTER ARGS... VAL).
+If FIX-RETURN is non-nil, then SETTER is not assumed to return VAL and
+instead the assignment is turned into (prog1 VAL (SETTER ARGS... VAL))
+so as to preserve the semantics of `setf'.
+
+\(fn NAME SETTER &optional FIX-RETURN)" nil t)
+
+(autoload 'setf "gv" "\
+Set each PLACE to the value of its VAL.
+This is a generalized version of `setq'; the PLACEs may be symbolic
+references such as (car x) or (aref x i), as well as plain symbols.
+For example, (setf (cadr x) y) is equivalent to (setcar (cdr x) y).
+The return value is the last VAL in the list.
+
+\(fn PLACE VAL PLACE VAL ...)" nil t)
+
+;;;***
+\f
+;;;### (autoloads (handwrite) "handwrite" "play/handwrite.el" (20318
+;;;;;; 5885))
;;; Generated autoloads from play/handwrite.el
(autoload 'handwrite "handwrite" "\
;;;***
\f
;;;### (autoloads (hanoi-unix-64 hanoi-unix hanoi) "hanoi" "play/hanoi.el"
-;;;;;; (20355 10021))
+;;;;;; (19989 53691))
;;; Generated autoloads from play/hanoi.el
(autoload 'hanoi "hanoi" "\
\f
;;;### (autoloads (mail-check-payment mail-add-payment-async mail-add-payment
;;;;;; hashcash-verify-payment hashcash-insert-payment-async hashcash-insert-payment)
-;;;;;; "hashcash" "mail/hashcash.el" (20355 10021))
+;;;;;; "hashcash" "mail/hashcash.el" (20356 35090))
;;; Generated autoloads from mail/hashcash.el
(autoload 'hashcash-insert-payment "hashcash" "\
;;;### (autoloads (scan-buf-previous-region scan-buf-next-region
;;;;;; scan-buf-move-to-region help-at-pt-display-when-idle help-at-pt-set-timer
;;;;;; help-at-pt-cancel-timer display-local-help help-at-pt-kbd-string
-;;;;;; help-at-pt-string) "help-at-pt" "help-at-pt.el" (20355 10021))
+;;;;;; help-at-pt-string) "help-at-pt" "help-at-pt.el" (20244 35516))
;;; Generated autoloads from help-at-pt.el
(autoload 'help-at-pt-string "help-at-pt" "\
;;;### (autoloads (doc-file-to-info doc-file-to-man describe-categories
;;;;;; describe-syntax describe-variable variable-at-point describe-function-1
;;;;;; find-lisp-object-file-name help-C-file-name describe-function)
-;;;;;; "help-fns" "help-fns.el" (20355 10021))
+;;;;;; "help-fns" "help-fns.el" (20438 21557))
;;; Generated autoloads from help-fns.el
(autoload 'describe-function "help-fns" "\
;;;***
\f
;;;### (autoloads (three-step-help) "help-macro" "help-macro.el"
-;;;;;; (20355 10021))
+;;;;;; (20253 50954))
;;; Generated autoloads from help-macro.el
(defvar three-step-help nil "\
;;;***
\f
-;;;### (autoloads (help-xref-on-pp help-insert-xref-button help-xref-button
-;;;;;; help-make-xrefs help-buffer help-setup-xref help-mode-finish
-;;;;;; help-mode-setup help-mode) "help-mode" "help-mode.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (help-bookmark-jump help-xref-on-pp help-insert-xref-button
+;;;;;; help-xref-button help-make-xrefs help-buffer help-setup-xref
+;;;;;; help-mode-finish help-mode-setup help-mode) "help-mode" "help-mode.el"
+;;;;;; (20446 34252))
;;; Generated autoloads from help-mode.el
(autoload 'help-mode "help-mode" "\
\(fn FROM TO)" nil nil)
+(autoload 'help-bookmark-jump "help-mode" "\
+Jump to help-mode bookmark BOOKMARK.
+Handler function for record returned by `help-bookmark-make-record'.
+BOOKMARK is a bookmark name or a bookmark record.
+
+\(fn BOOKMARK)" nil nil)
+
;;;***
\f
;;;### (autoloads (Helper-help Helper-describe-bindings) "helper"
-;;;;;; "emacs-lisp/helper.el" (20355 10021))
+;;;;;; "emacs-lisp/helper.el" (20244 35516))
;;; Generated autoloads from emacs-lisp/helper.el
(autoload 'Helper-describe-bindings "helper" "\
;;;***
\f
;;;### (autoloads (hexlify-buffer hexl-find-file hexl-mode) "hexl"
-;;;;;; "hexl.el" (20420 41510))
+;;;;;; "hexl.el" (20420 52684))
;;; Generated autoloads from hexl.el
(autoload 'hexl-mode "hexl" "\
;;;### (autoloads (hi-lock-write-interactive-patterns hi-lock-unface-buffer
;;;;;; hi-lock-face-phrase-buffer hi-lock-face-buffer hi-lock-line-face-buffer
;;;;;; global-hi-lock-mode hi-lock-mode) "hi-lock" "hi-lock.el"
-;;;;;; (20410 5673))
+;;;;;; (20412 11425))
;;; Generated autoloads from hi-lock.el
(autoload 'hi-lock-mode "hi-lock" "\
;;;***
\f
;;;### (autoloads (hide-ifdef-mode) "hideif" "progmodes/hideif.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from progmodes/hideif.el
(autoload 'hide-ifdef-mode "hideif" "\
;;;***
\f
;;;### (autoloads (turn-off-hideshow hs-minor-mode) "hideshow" "progmodes/hideshow.el"
-;;;;;; (20356 55829))
+;;;;;; (20359 18671))
;;; Generated autoloads from progmodes/hideshow.el
(defvar hs-special-modes-alist (mapcar 'purecopy '((c-mode "{" "}" "/[*/]" nil nil) (c++-mode "{" "}" "/[*/]" nil nil) (bibtex-mode ("@\\S(*\\(\\s(\\)" 1)) (java-mode "{" "}" "/[*/]" nil nil) (js-mode "{" "}" "/[*/]" nil))) "\
;;;;;; highlight-compare-buffers highlight-changes-rotate-faces
;;;;;; highlight-changes-previous-change highlight-changes-next-change
;;;;;; highlight-changes-remove-highlight highlight-changes-visible-mode
-;;;;;; highlight-changes-mode) "hilit-chg" "hilit-chg.el" (20355
-;;;;;; 10021))
+;;;;;; highlight-changes-mode) "hilit-chg" "hilit-chg.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from hilit-chg.el
(autoload 'highlight-changes-mode "hilit-chg" "\
;;;;;; hippie-expand-ignore-buffers hippie-expand-max-buffers hippie-expand-no-restriction
;;;;;; hippie-expand-dabbrev-as-symbol hippie-expand-dabbrev-skip-space
;;;;;; hippie-expand-verbose hippie-expand-try-functions-list) "hippie-exp"
-;;;;;; "hippie-exp.el" (20355 10021))
+;;;;;; "hippie-exp.el" (20244 35516))
;;; Generated autoloads from hippie-exp.el
(defvar hippie-expand-try-functions-list '(try-complete-file-name-partially try-complete-file-name try-expand-all-abbrevs try-expand-list try-expand-line try-expand-dabbrev try-expand-dabbrev-all-buffers try-expand-dabbrev-from-kill try-complete-lisp-symbol-partially try-complete-lisp-symbol) "\
Make it use the expansion functions in TRY-LIST. An optional second
argument VERBOSE non-nil makes the function verbose.
-\(fn TRY-LIST &optional VERBOSE)" nil (quote macro))
+\(fn TRY-LIST &optional VERBOSE)" nil t)
;;;***
\f
;;;### (autoloads (global-hl-line-mode hl-line-mode) "hl-line" "hl-line.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from hl-line.el
(autoload 'hl-line-mode "hl-line" "\
;;;;;; holiday-bahai-holidays holiday-islamic-holidays holiday-christian-holidays
;;;;;; holiday-hebrew-holidays holiday-other-holidays holiday-local-holidays
;;;;;; holiday-oriental-holidays holiday-general-holidays) "holidays"
-;;;;;; "calendar/holidays.el" (20390 20388))
+;;;;;; "calendar/holidays.el" (20412 11425))
;;; Generated autoloads from calendar/holidays.el
(define-obsolete-variable-alias 'general-holidays 'holiday-general-holidays "23.1")
;;;***
\f
-;;;### (autoloads (html2text) "html2text" "gnus/html2text.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (html2text) "html2text" "gnus/html2text.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from gnus/html2text.el
(autoload 'html2text "html2text" "\
;;;***
\f
;;;### (autoloads (htmlfontify-copy-and-link-dir htmlfontify-buffer)
-;;;;;; "htmlfontify" "htmlfontify.el" (20355 10021))
+;;;;;; "htmlfontify" "htmlfontify.el" (20331 12564))
;;; Generated autoloads from htmlfontify.el
(autoload 'htmlfontify-buffer "htmlfontify" "\
\(fn SRCDIR DSTDIR &optional F-EXT L-EXT)" t nil)
;;;***
-\f
-;;;### (autoloads (define-ibuffer-filter define-ibuffer-op define-ibuffer-sorter
-;;;;;; define-ibuffer-column) "ibuf-macs" "ibuf-macs.el" (20406
-;;;;;; 8611))
-;;; Generated autoloads from ibuf-macs.el
-
-(autoload 'define-ibuffer-column "ibuf-macs" "\
-Define a column SYMBOL for use with `ibuffer-formats'.
-
-BODY will be called with `buffer' bound to the buffer object, and
-`mark' bound to the current mark on the buffer. The original ibuffer
-buffer will be bound to `ibuffer-buf'.
-
-If NAME is given, it will be used as a title for the column.
-Otherwise, the title will default to a capitalized version of the
-SYMBOL's name. PROPS is a plist of additional properties to add to
-the text, such as `mouse-face'. And SUMMARIZER, if given, is a
-function which will be passed a list of all the strings in its column;
-it should return a string to display at the bottom.
-
-If HEADER-MOUSE-MAP is given, it will be used as a keymap for the
-title of the column.
-
-Note that this macro expands into a `defun' for a function named
-ibuffer-make-column-NAME. If INLINE is non-nil, then the form will be
-inlined into the compiled format versions. This means that if you
-change its definition, you should explicitly call
-`ibuffer-recompile-formats'.
-
-\(fn SYMBOL (&key NAME INLINE PROPS SUMMARIZER) &rest BODY)" nil (quote macro))
-
-(put 'define-ibuffer-column 'lisp-indent-function 'defun)
-
-(autoload 'define-ibuffer-sorter "ibuf-macs" "\
-Define a method of sorting named NAME.
-DOCUMENTATION is the documentation of the function, which will be called
-`ibuffer-do-sort-by-NAME'.
-DESCRIPTION is a short string describing the sorting method.
-
-For sorting, the forms in BODY will be evaluated with `a' bound to one
-buffer object, and `b' bound to another. BODY should return a non-nil
-value if and only if `a' is \"less than\" `b'.
-
-\(fn NAME DOCUMENTATION (&key DESCRIPTION) &rest BODY)" nil (quote macro))
-
-(put 'define-ibuffer-sorter 'doc-string-elt '2)
-
-(put 'define-ibuffer-sorter 'lisp-indent-function '1)
-
-(autoload 'define-ibuffer-op "ibuf-macs" "\
-Generate a function which operates on a buffer.
-OP becomes the name of the function; if it doesn't begin with
-`ibuffer-do-', then that is prepended to it.
-When an operation is performed, this function will be called once for
-each marked buffer, with that buffer current.
-
-ARGS becomes the formal parameters of the function.
-DOCUMENTATION becomes the docstring of the function.
-INTERACTIVE becomes the interactive specification of the function.
-MARK describes which type of mark (:deletion, or nil) this operation
-uses. :deletion means the function operates on buffers marked for
-deletion, otherwise it acts on normally marked buffers.
-MODIFIER-P describes how the function modifies buffers. This is used
-to set the modification flag of the Ibuffer buffer itself. Valid
-values are:
- nil - the function never modifiers buffers
- t - the function it always modifies buffers
- :maybe - attempt to discover this information by comparing the
- buffer's modification flag.
-DANGEROUS is a boolean which should be set if the user should be
-prompted before performing this operation.
-OPSTRING is a string which will be displayed to the user after the
-operation is complete, in the form:
- \"Operation complete; OPSTRING x buffers\"
-ACTIVE-OPSTRING is a string which will be displayed to the user in a
-confirmation message, in the form:
- \"Really ACTIVE-OPSTRING x buffers?\"
-COMPLEX means this function is special; see the source code of this
-macro for exactly what it does.
-
-\(fn OP ARGS DOCUMENTATION (&key INTERACTIVE MARK MODIFIER-P DANGEROUS OPSTRING ACTIVE-OPSTRING COMPLEX) &rest BODY)" nil (quote macro))
-
-(put 'define-ibuffer-op 'doc-string-elt '3)
-
-(put 'define-ibuffer-op 'lisp-indent-function '2)
-
-(autoload 'define-ibuffer-filter "ibuf-macs" "\
-Define a filter named NAME.
-DOCUMENTATION is the documentation of the function.
-READER is a form which should read a qualifier from the user.
-DESCRIPTION is a short string describing the filter.
-
-BODY should contain forms which will be evaluated to test whether or
-not a particular buffer should be displayed or not. The forms in BODY
-will be evaluated with BUF bound to the buffer object, and QUALIFIER
-bound to the current value of the filter.
-
-\(fn NAME DOCUMENTATION (&key READER DESCRIPTION) &rest BODY)" nil (quote macro))
-
-(put 'define-ibuffer-filter 'doc-string-elt '2)
-
-(put 'define-ibuffer-filter 'lisp-indent-function '2)
;;;***
\f
+;;;### (autoloads nil "ibuf-macs" "ibuf-macs.el" (20412 11425))
+;;; Generated autoloads from ibuf-macs.el
+\f
;;;### (autoloads (ibuffer ibuffer-other-window ibuffer-list-buffers)
-;;;;;; "ibuffer" "ibuffer.el" (20383 47352))
+;;;;;; "ibuffer" "ibuffer.el" (20412 11425))
;;; Generated autoloads from ibuffer.el
(autoload 'ibuffer-list-buffers "ibuffer" "\
\f
;;;### (autoloads (icalendar-import-buffer icalendar-import-file
;;;;;; icalendar-export-region icalendar-export-file) "icalendar"
-;;;;;; "calendar/icalendar.el" (20421 62373))
+;;;;;; "calendar/icalendar.el" (20434 28080))
;;; Generated autoloads from calendar/icalendar.el
(autoload 'icalendar-export-file "icalendar" "\
;;;***
\f
-;;;### (autoloads (icomplete-mode) "icomplete" "icomplete.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (icomplete-mode) "icomplete" "icomplete.el" (20318
+;;;;;; 5885))
;;; Generated autoloads from icomplete.el
(defvar icomplete-mode nil "\
;;;***
\f
-;;;### (autoloads (icon-mode) "icon" "progmodes/icon.el" (20355 10021))
+;;;### (autoloads (icon-mode) "icon" "progmodes/icon.el" (20356 35090))
;;; Generated autoloads from progmodes/icon.el
(autoload 'icon-mode "icon" "\
;;;***
\f
;;;### (autoloads (idlwave-shell) "idlw-shell" "progmodes/idlw-shell.el"
-;;;;;; (20394 17446))
+;;;;;; (20428 57510))
;;; Generated autoloads from progmodes/idlw-shell.el
(autoload 'idlwave-shell "idlw-shell" "\
;;;***
\f
;;;### (autoloads (idlwave-mode) "idlwave" "progmodes/idlwave.el"
-;;;;;; (20387 44199))
+;;;;;; (20412 11425))
;;; Generated autoloads from progmodes/idlwave.el
(autoload 'idlwave-mode "idlwave" "\
;;;;;; ido-find-alternate-file ido-find-file-other-window ido-find-file
;;;;;; ido-find-file-in-dir ido-switch-buffer-other-frame ido-insert-buffer
;;;;;; ido-kill-buffer ido-display-buffer ido-switch-buffer-other-window
-;;;;;; ido-switch-buffer ido-mode ido-mode) "ido" "ido.el" (20387
-;;;;;; 44199))
+;;;;;; ido-switch-buffer ido-mode ido-mode) "ido" "ido.el" (20451
+;;;;;; 20881))
;;; Generated autoloads from ido.el
(defvar ido-mode nil "\
RET Select the buffer at the front of the list of matches. If the
list is empty, possibly prompt to create new buffer.
-\\[ido-select-text] Select the current prompt as the buffer.
-If no buffer is found, prompt for a new one.
+\\[ido-select-text] Use the current input string verbatim.
\\[ido-next-match] Put the first element at the end of the list.
\\[ido-prev-match] Put the last element at the start of the list.
RET Select the file at the front of the list of matches. If the
list is empty, possibly prompt to create new file.
-\\[ido-select-text] Select the current prompt as the buffer or file.
-If no buffer or file is found, prompt for a new one.
+\\[ido-select-text] Use the current input string verbatim.
\\[ido-next-match] Put the first element at the end of the list.
\\[ido-prev-match] Put the last element at the start of the list.
matches all files. If there is only one match, select that file.
If there is no common suffix, show a list of all matching files
in a separate window.
+\\[ido-magic-delete-char] Open the specified directory in Dired mode.
\\[ido-edit-input] Edit input string (including directory).
\\[ido-prev-work-directory] or \\[ido-next-work-directory] go to previous/next directory in work directory history.
\\[ido-merge-work-directories] search for file in the work directory history.
;;;***
\f
-;;;### (autoloads (ielm) "ielm" "ielm.el" (20355 10021))
+;;;### (autoloads (ielm) "ielm" "ielm.el" (20244 35516))
;;; Generated autoloads from ielm.el
(autoload 'ielm "ielm" "\
;;;***
\f
-;;;### (autoloads (iimage-mode) "iimage" "iimage.el" (20355 10021))
+;;;### (autoloads (iimage-mode) "iimage" "iimage.el" (20276 3849))
;;; Generated autoloads from iimage.el
(define-obsolete-function-alias 'turn-on-iimage-mode 'iimage-mode "24.1")
;;;;;; create-image image-type-auto-detected-p image-type-available-p
;;;;;; image-type image-type-from-file-name image-type-from-file-header
;;;;;; image-type-from-buffer image-type-from-data) "image" "image.el"
-;;;;;; (20423 43129))
+;;;;;; (20438 17064))
;;; Generated autoloads from image.el
(autoload 'image-type-from-data "image" "\
;;;;;; image-dired-jump-thumbnail-buffer image-dired-delete-tag
;;;;;; image-dired-tag-files image-dired-show-all-from-dir image-dired-display-thumbs
;;;;;; image-dired-dired-with-window-configuration image-dired-dired-toggle-marked-thumbs)
-;;;;;; "image-dired" "image-dired.el" (20355 10021))
+;;;;;; "image-dired" "image-dired.el" (20244 35516))
;;; Generated autoloads from image-dired.el
(autoload 'image-dired-dired-toggle-marked-thumbs "image-dired" "\
\f
;;;### (autoloads (auto-image-file-mode insert-image-file image-file-name-regexp
;;;;;; image-file-name-regexps image-file-name-extensions) "image-file"
-;;;;;; "image-file.el" (20355 10021))
+;;;;;; "image-file.el" (20244 35516))
;;; Generated autoloads from image-file.el
(defvar image-file-name-extensions (purecopy '("png" "jpeg" "jpg" "gif" "tiff" "tif" "xbm" "xpm" "pbm" "pgm" "ppm" "pnm" "svg")) "\
;;;***
\f
;;;### (autoloads (image-bookmark-jump image-mode-as-text image-minor-mode
-;;;;;; image-mode) "image-mode" "image-mode.el" (20420 41510))
+;;;;;; image-mode) "image-mode" "image-mode.el" (20420 52684))
;;; Generated autoloads from image-mode.el
(autoload 'image-mode "image-mode" "\
;;;***
\f
;;;### (autoloads (imenu imenu-add-menubar-index imenu-add-to-menubar
-;;;;;; imenu-sort-function) "imenu" "imenu.el" (20393 22044))
+;;;;;; imenu-sort-function) "imenu" "imenu.el" (20412 11425))
;;; Generated autoloads from imenu.el
(defvar imenu-sort-function nil "\
\f
;;;### (autoloads (indian-2-column-to-ucs-region in-is13194-pre-write-conversion
;;;;;; in-is13194-post-read-conversion indian-compose-string indian-compose-region)
-;;;;;; "ind-util" "language/ind-util.el" (20355 10021))
+;;;;;; "ind-util" "language/ind-util.el" (20244 35516))
;;; Generated autoloads from language/ind-util.el
(autoload 'indian-compose-region "ind-util" "\
\f
;;;### (autoloads (inferior-lisp inferior-lisp-prompt inferior-lisp-load-command
;;;;;; inferior-lisp-program inferior-lisp-filter-regexp) "inf-lisp"
-;;;;;; "progmodes/inf-lisp.el" (20355 10021))
+;;;;;; "progmodes/inf-lisp.el" (20356 35090))
;;; Generated autoloads from progmodes/inf-lisp.el
(defvar inferior-lisp-filter-regexp (purecopy "\\`\\s *\\(:\\(\\w\\|\\s_\\)\\)?\\s *\\'") "\
;;;;;; Info-goto-emacs-key-command-node Info-goto-emacs-command-node
;;;;;; Info-mode info-finder info-apropos Info-index Info-directory
;;;;;; Info-on-current-buffer info-standalone info-emacs-bug info-emacs-manual
-;;;;;; info info-other-window) "info" "info.el" (20420 41510))
+;;;;;; info info-other-window) "info" "info.el" (20434 28080))
;;; Generated autoloads from info.el
(autoload 'info-other-window "info" "\
\f
;;;### (autoloads (info-complete-file info-complete-symbol info-lookup-file
;;;;;; info-lookup-symbol info-lookup-reset) "info-look" "info-look.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from info-look.el
(autoload 'info-lookup-reset "info-look" "\
\f
;;;### (autoloads (info-xref-docstrings info-xref-check-all-custom
;;;;;; info-xref-check-all info-xref-check) "info-xref" "info-xref.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from info-xref.el
(autoload 'info-xref-check "info-xref" "\
;;;***
\f
;;;### (autoloads (batch-info-validate Info-validate Info-split Info-split-threshold
-;;;;;; Info-tagify) "informat" "informat.el" (20355 10021))
+;;;;;; Info-tagify) "informat" "informat.el" (20244 35516))
;;; Generated autoloads from informat.el
(autoload 'Info-tagify "informat" "\
\f
;;;### (autoloads (isearch-process-search-multibyte-characters isearch-toggle-input-method
;;;;;; isearch-toggle-specified-input-method) "isearch-x" "international/isearch-x.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from international/isearch-x.el
(autoload 'isearch-toggle-specified-input-method "isearch-x" "\
;;;***
\f
-;;;### (autoloads (isearchb-activate) "isearchb" "isearchb.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (isearchb-activate) "isearchb" "isearchb.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from isearchb.el
(autoload 'isearchb-activate "isearchb" "\
;;;### (autoloads (iso-cvt-define-menu iso-cvt-write-only iso-cvt-read-only
;;;;;; iso-sgml2iso iso-iso2sgml iso-iso2duden iso-iso2gtex iso-gtex2iso
;;;;;; iso-tex2iso iso-iso2tex iso-german iso-spanish) "iso-cvt"
-;;;;;; "international/iso-cvt.el" (20355 10021))
+;;;;;; "international/iso-cvt.el" (20244 35516))
;;; Generated autoloads from international/iso-cvt.el
(autoload 'iso-spanish "iso-cvt" "\
;;;***
\f
;;;### (autoloads nil "iso-transl" "international/iso-transl.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from international/iso-transl.el
(or key-translation-map (setq key-translation-map (make-sparse-keymap)))
(define-key key-translation-map "\C-x8" 'iso-transl-ctl-x-8-map)
;;;;;; ispell-complete-word ispell-continue ispell-buffer ispell-comments-and-strings
;;;;;; ispell-region ispell-change-dictionary ispell-kill-ispell
;;;;;; ispell-help ispell-pdict-save ispell-word ispell-personal-dictionary)
-;;;;;; "ispell" "textmodes/ispell.el" (20423 17700))
+;;;;;; "ispell" "textmodes/ispell.el" (20428 57510))
;;; Generated autoloads from textmodes/ispell.el
(put 'ispell-check-comments 'safe-local-variable (lambda (a) (memq a '(nil t exclusive))))
;;;***
\f
-;;;### (autoloads (iswitchb-mode) "iswitchb" "iswitchb.el" (20387
-;;;;;; 44199))
+;;;### (autoloads (iswitchb-mode) "iswitchb" "iswitchb.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from iswitchb.el
(defvar iswitchb-mode nil "\
;;;### (autoloads (read-hiragana-string japanese-zenkaku-region japanese-hankaku-region
;;;;;; japanese-hiragana-region japanese-katakana-region japanese-zenkaku
;;;;;; japanese-hankaku japanese-hiragana japanese-katakana setup-japanese-environment-internal)
-;;;;;; "japan-util" "language/japan-util.el" (20355 10021))
+;;;;;; "japan-util" "language/japan-util.el" (20244 35516))
;;; Generated autoloads from language/japan-util.el
(autoload 'setup-japanese-environment-internal "japan-util" "\
;;;***
\f
;;;### (autoloads (jka-compr-uninstall jka-compr-handler) "jka-compr"
-;;;;;; "jka-compr.el" (20355 10021))
+;;;;;; "jka-compr.el" (20318 5885))
;;; Generated autoloads from jka-compr.el
(defvar jka-compr-inhibit nil "\
;;;***
\f
-;;;### (autoloads (js-mode) "js" "progmodes/js.el" (20415 53309))
+;;;### (autoloads (js-mode) "js" "progmodes/js.el" (20415 57974))
;;; Generated autoloads from progmodes/js.el
(autoload 'js-mode "js" "\
\f
;;;### (autoloads (keypad-setup keypad-numlock-shifted-setup keypad-shifted-setup
;;;;;; keypad-numlock-setup keypad-setup) "keypad" "emulation/keypad.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from emulation/keypad.el
(defvar keypad-setup nil "\
;;;***
\f
;;;### (autoloads (kinsoku) "kinsoku" "international/kinsoku.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from international/kinsoku.el
(autoload 'kinsoku "kinsoku" "\
;;;***
\f
-;;;### (autoloads (kkc-region) "kkc" "international/kkc.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (kkc-region) "kkc" "international/kkc.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from international/kkc.el
(defvar kkc-after-update-conversion-functions nil "\
;;;### (autoloads (kmacro-end-call-mouse kmacro-end-and-call-macro
;;;;;; kmacro-end-or-call-macro kmacro-start-macro-or-insert-counter
;;;;;; kmacro-call-macro kmacro-end-macro kmacro-start-macro kmacro-exec-ring-item)
-;;;;;; "kmacro" "kmacro.el" (20388 65061))
+;;;;;; "kmacro" "kmacro.el" (20412 11425))
;;; Generated autoloads from kmacro.el
(global-set-key "\C-x(" 'kmacro-start-macro)
(global-set-key "\C-x)" 'kmacro-end-macro)
;;;***
\f
;;;### (autoloads (setup-korean-environment-internal) "korea-util"
-;;;;;; "language/korea-util.el" (20355 10021))
+;;;;;; "language/korea-util.el" (20356 35090))
;;; Generated autoloads from language/korea-util.el
(defvar default-korean-keyboard (purecopy (if (string-match "3" (or (getenv "HANGUL_KEYBOARD_TYPE") "")) "3" "")) "\
;;;***
\f
;;;### (autoloads (landmark landmark-test-run) "landmark" "play/landmark.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from play/landmark.el
(defalias 'landmark-repeat 'landmark-test-run)
\f
;;;### (autoloads (lao-compose-region lao-composition-function lao-transcribe-roman-to-lao-string
;;;;;; lao-transcribe-single-roman-syllable-to-lao lao-compose-string)
-;;;;;; "lao-util" "language/lao-util.el" (20355 10021))
+;;;;;; "lao-util" "language/lao-util.el" (20244 35516))
;;; Generated autoloads from language/lao-util.el
(autoload 'lao-compose-string "lao-util" "\
\f
;;;### (autoloads (latexenc-find-file-coding-system latexenc-coding-system-to-inputenc
;;;;;; latexenc-inputenc-to-coding-system latex-inputenc-coding-alist)
-;;;;;; "latexenc" "international/latexenc.el" (20355 10021))
+;;;;;; "latexenc" "international/latexenc.el" (20244 35516))
;;; Generated autoloads from international/latexenc.el
(defvar latex-inputenc-coding-alist (purecopy '(("ansinew" . windows-1252) ("applemac" . mac-roman) ("ascii" . us-ascii) ("cp1250" . windows-1250) ("cp1252" . windows-1252) ("cp1257" . cp1257) ("cp437de" . cp437) ("cp437" . cp437) ("cp850" . cp850) ("cp852" . cp852) ("cp858" . cp858) ("cp865" . cp865) ("latin1" . iso-8859-1) ("latin2" . iso-8859-2) ("latin3" . iso-8859-3) ("latin4" . iso-8859-4) ("latin5" . iso-8859-5) ("latin9" . iso-8859-15) ("next" . next) ("utf8" . utf-8) ("utf8x" . utf-8))) "\
;;;***
\f
;;;### (autoloads (latin1-display-ucs-per-lynx latin1-display latin1-display)
-;;;;;; "latin1-disp" "international/latin1-disp.el" (20355 10021))
+;;;;;; "latin1-disp" "international/latin1-disp.el" (20244 35516))
;;; Generated autoloads from international/latin1-disp.el
(defvar latin1-display nil "\
;;;***
\f
;;;### (autoloads (ld-script-mode) "ld-script" "progmodes/ld-script.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from progmodes/ld-script.el
(autoload 'ld-script-mode "ld-script" "\
;;;***
\f
-;;;### (autoloads (ledit-from-lisp-mode ledit-mode) "ledit" "ledit.el"
-;;;;;; (20355 10021))
-;;; Generated autoloads from ledit.el
-
-(defconst ledit-save-files t "\
-*Non-nil means Ledit should save files before transferring to Lisp.")
-
-(defconst ledit-go-to-lisp-string "%?lisp" "\
-*Shell commands to execute to resume Lisp job.")
-
-(defconst ledit-go-to-liszt-string "%?liszt" "\
-*Shell commands to execute to resume Lisp compiler job.")
-
-(autoload 'ledit-mode "ledit" "\
-\\<ledit-mode-map>Major mode for editing text and stuffing it to a Lisp job.
-Like Lisp mode, plus these special commands:
- \\[ledit-save-defun] -- record defun at or after point
- for later transmission to Lisp job.
- \\[ledit-save-region] -- record region for later transmission to Lisp job.
- \\[ledit-go-to-lisp] -- transfer to Lisp job and transmit saved text.
- \\[ledit-go-to-liszt] -- transfer to Liszt (Lisp compiler) job
- and transmit saved text.
-
-\\{ledit-mode-map}
-To make Lisp mode automatically change to Ledit mode,
-do (setq lisp-mode-hook 'ledit-from-lisp-mode)
-
-\(fn)" t nil)
-
-(autoload 'ledit-from-lisp-mode "ledit" "\
-
-
-\(fn)" nil nil)
-
-;;;***
-\f
-;;;### (autoloads (life) "life" "play/life.el" (20355 10021))
+;;;### (autoloads (life) "life" "play/life.el" (20244 35516))
;;; Generated autoloads from play/life.el
(autoload 'life "life" "\
;;;***
\f
;;;### (autoloads (global-linum-mode linum-mode linum-format) "linum"
-;;;;;; "linum.el" (20355 10021))
+;;;;;; "linum.el" (20244 35516))
;;; Generated autoloads from linum.el
(defvar linum-format 'dynamic "\
;;;***
\f
-;;;### (autoloads (unload-feature) "loadhist" "loadhist.el" (20399
-;;;;;; 35365))
+;;;### (autoloads (unload-feature) "loadhist" "loadhist.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from loadhist.el
(autoload 'unload-feature "loadhist" "\
;;;***
\f
;;;### (autoloads (locate-with-filter locate locate-ls-subdir-switches)
-;;;;;; "locate" "locate.el" (20355 10021))
+;;;;;; "locate" "locate.el" (20244 35516))
;;; Generated autoloads from locate.el
(defvar locate-ls-subdir-switches (purecopy "-al") "\
;;;***
\f
-;;;### (autoloads (log-edit) "log-edit" "vc/log-edit.el" (20399 35365))
+;;;### (autoloads (log-edit) "log-edit" "vc/log-edit.el" (20412 11425))
;;; Generated autoloads from vc/log-edit.el
(autoload 'log-edit "log-edit" "\
;;;***
\f
-;;;### (autoloads (log-view-mode) "log-view" "vc/log-view.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (log-view-mode) "log-view" "vc/log-view.el" (20290
+;;;;;; 33419))
;;; Generated autoloads from vc/log-view.el
(autoload 'log-view-mode "log-view" "\
;;;***
\f
-;;;### (autoloads (longlines-mode) "longlines" "longlines.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (longlines-mode) "longlines" "longlines.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from longlines.el
(autoload 'longlines-mode "longlines" "\
;;;***
\f
;;;### (autoloads (print-region lpr-region print-buffer lpr-buffer
-;;;;;; lpr-command lpr-switches printer-name) "lpr" "lpr.el" (20355
-;;;;;; 10021))
+;;;;;; lpr-command lpr-switches printer-name) "lpr" "lpr.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from lpr.el
(defvar lpr-windows-system (memq system-type '(ms-dos windows-nt)) "\
;;;***
\f
;;;### (autoloads (ls-lisp-support-shell-wildcards) "ls-lisp" "ls-lisp.el"
-;;;;;; (20355 10021))
+;;;;;; (20276 3849))
;;; Generated autoloads from ls-lisp.el
(defvar ls-lisp-support-shell-wildcards t "\
;;;***
\f
-;;;### (autoloads (lunar-phases) "lunar" "calendar/lunar.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (lunar-phases) "lunar" "calendar/lunar.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from calendar/lunar.el
(autoload 'lunar-phases "lunar" "\
;;;***
\f
-;;;### (autoloads (m4-mode) "m4-mode" "progmodes/m4-mode.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (m4-mode) "m4-mode" "progmodes/m4-mode.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from progmodes/m4-mode.el
(autoload 'm4-mode "m4-mode" "\
;;;***
\f
;;;### (autoloads (macroexpand-all) "macroexp" "emacs-lisp/macroexp.el"
-;;;;;; (20421 62373))
+;;;;;; (20451 34676))
;;; Generated autoloads from emacs-lisp/macroexp.el
(autoload 'macroexpand-all "macroexp" "\
;;;***
\f
;;;### (autoloads (apply-macro-to-region-lines kbd-macro-query insert-kbd-macro
-;;;;;; name-last-kbd-macro) "macros" "macros.el" (20355 10021))
+;;;;;; name-last-kbd-macro) "macros" "macros.el" (20244 35516))
;;; Generated autoloads from macros.el
(autoload 'name-last-kbd-macro "macros" "\
;;;***
\f
;;;### (autoloads (what-domain mail-extract-address-components) "mail-extr"
-;;;;;; "mail/mail-extr.el" (20355 10021))
+;;;;;; "mail/mail-extr.el" (20356 35090))
;;; Generated autoloads from mail/mail-extr.el
(autoload 'mail-extract-address-components "mail-extr" "\
\f
;;;### (autoloads (mail-hist-put-headers-into-history mail-hist-keep-history
;;;;;; mail-hist-enable mail-hist-define-keys) "mail-hist" "mail/mail-hist.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from mail/mail-hist.el
(autoload 'mail-hist-define-keys "mail-hist" "\
;;;### (autoloads (mail-fetch-field mail-unquote-printable-region
;;;;;; mail-unquote-printable mail-quote-printable-region mail-quote-printable
;;;;;; mail-file-babyl-p mail-dont-reply-to-names mail-use-rfc822)
-;;;;;; "mail-utils" "mail/mail-utils.el" (20355 10021))
+;;;;;; "mail-utils" "mail/mail-utils.el" (20318 5885))
;;; Generated autoloads from mail/mail-utils.el
(defvar mail-use-rfc822 nil "\
;;;***
\f
;;;### (autoloads (define-mail-abbrev build-mail-abbrevs mail-abbrevs-setup
-;;;;;; mail-abbrevs-mode) "mailabbrev" "mail/mailabbrev.el" (20387
-;;;;;; 44199))
+;;;;;; mail-abbrevs-mode) "mailabbrev" "mail/mailabbrev.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from mail/mailabbrev.el
(defvar mail-abbrevs-mode nil "\
\f
;;;### (autoloads (mail-complete mail-completion-at-point-function
;;;;;; define-mail-alias expand-mail-aliases mail-complete-style)
-;;;;;; "mailalias" "mail/mailalias.el" (20355 10021))
+;;;;;; "mailalias" "mail/mailalias.el" (20244 35516))
;;; Generated autoloads from mail/mailalias.el
(defvar mail-complete-style 'angles "\
;;;***
\f
;;;### (autoloads (mailclient-send-it) "mailclient" "mail/mailclient.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from mail/mailclient.el
(autoload 'mailclient-send-it "mailclient" "\
\f
;;;### (autoloads (makefile-imake-mode makefile-bsdmake-mode makefile-makepp-mode
;;;;;; makefile-gmake-mode makefile-automake-mode makefile-mode)
-;;;;;; "make-mode" "progmodes/make-mode.el" (20392 30149))
+;;;;;; "make-mode" "progmodes/make-mode.el" (20412 11425))
;;; Generated autoloads from progmodes/make-mode.el
(autoload 'makefile-mode "make-mode" "\
;;;***
\f
-;;;### (autoloads (make-command-summary) "makesum" "makesum.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (make-command-summary) "makesum" "makesum.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from makesum.el
(autoload 'make-command-summary "makesum" "\
;;;***
\f
;;;### (autoloads (Man-bookmark-jump man-follow man) "man" "man.el"
-;;;;;; (20390 20388))
+;;;;;; (20412 11425))
;;; Generated autoloads from man.el
(defalias 'manual-entry 'man)
;;;***
\f
-;;;### (autoloads (master-mode) "master" "master.el" (20355 10021))
+;;;### (autoloads (master-mode) "master" "master.el" (20244 35516))
;;; Generated autoloads from master.el
(autoload 'master-mode "master" "\
;;;***
\f
;;;### (autoloads (minibuffer-depth-indicate-mode) "mb-depth" "mb-depth.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from mb-depth.el
(defvar minibuffer-depth-indicate-mode nil "\
;;;;;; message-forward-make-body message-forward message-recover
;;;;;; message-supersede message-cancel-news message-followup message-wide-reply
;;;;;; message-reply message-news message-mail message-mode) "message"
-;;;;;; "gnus/message.el" (20355 10021))
+;;;;;; "gnus/message.el" (20290 33419))
;;; Generated autoloads from gnus/message.el
(define-mail-user-agent 'message-user-agent 'message-mail 'message-send-and-exit 'message-kill-buffer 'message-send-hook)
;;;***
\f
;;;### (autoloads (metapost-mode metafont-mode) "meta-mode" "progmodes/meta-mode.el"
-;;;;;; (20399 35365))
+;;;;;; (20412 11425))
;;; Generated autoloads from progmodes/meta-mode.el
(autoload 'metafont-mode "meta-mode" "\
\f
;;;### (autoloads (metamail-region metamail-buffer metamail-interpret-body
;;;;;; metamail-interpret-header) "metamail" "mail/metamail.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from mail/metamail.el
(autoload 'metamail-interpret-header "metamail" "\
\f
;;;### (autoloads (mh-fully-kill-draft mh-send-letter mh-user-agent-compose
;;;;;; mh-smail-batch mh-smail-other-window mh-smail) "mh-comp"
-;;;;;; "mh-e/mh-comp.el" (20355 10021))
+;;;;;; "mh-e/mh-comp.el" (20244 35516))
;;; Generated autoloads from mh-e/mh-comp.el
(autoload 'mh-smail "mh-comp" "\
;;;***
\f
-;;;### (autoloads (mh-version) "mh-e" "mh-e/mh-e.el" (20355 10021))
+;;;### (autoloads (mh-version) "mh-e" "mh-e/mh-e.el" (20244 35516))
;;; Generated autoloads from mh-e/mh-e.el
(put 'mh-progs 'risky-local-variable t)
;;;***
\f
;;;### (autoloads (mh-folder-mode mh-nmail mh-rmail) "mh-folder"
-;;;;;; "mh-e/mh-folder.el" (20371 55972))
+;;;;;; "mh-e/mh-folder.el" (20373 41604))
;;; Generated autoloads from mh-e/mh-folder.el
(autoload 'mh-rmail "mh-folder" "\
;;;***
\f
;;;### (autoloads (midnight-delay-set clean-buffer-list) "midnight"
-;;;;;; "midnight.el" (20355 10021))
+;;;;;; "midnight.el" (20244 35516))
;;; Generated autoloads from midnight.el
(autoload 'clean-buffer-list "midnight" "\
;;;***
\f
;;;### (autoloads (minibuffer-electric-default-mode) "minibuf-eldef"
-;;;;;; "minibuf-eldef.el" (20355 10021))
+;;;;;; "minibuf-eldef.el" (20356 35090))
;;; Generated autoloads from minibuf-eldef.el
(defvar minibuffer-electric-default-mode nil "\
;;;***
\f
;;;### (autoloads (list-dynamic-libraries butterfly) "misc" "misc.el"
-;;;;;; (20356 27828))
+;;;;;; (20356 35090))
;;; Generated autoloads from misc.el
(autoload 'butterfly "misc" "\
\f
;;;### (autoloads (multi-isearch-files-regexp multi-isearch-files
;;;;;; multi-isearch-buffers-regexp multi-isearch-buffers multi-isearch-setup)
-;;;;;; "misearch" "misearch.el" (20420 41510))
+;;;;;; "misearch" "misearch.el" (20420 52684))
;;; Generated autoloads from misearch.el
(add-hook 'isearch-mode-hook 'multi-isearch-setup)
;;;***
\f
;;;### (autoloads (mixal-mode) "mixal-mode" "progmodes/mixal-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from progmodes/mixal-mode.el
(autoload 'mixal-mode "mixal-mode" "\
;;;***
\f
;;;### (autoloads (mm-default-file-encoding) "mm-encode" "gnus/mm-encode.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/mm-encode.el
(autoload 'mm-default-file-encoding "mm-encode" "\
;;;***
\f
;;;### (autoloads (mm-inline-external-body mm-extern-cache-contents)
-;;;;;; "mm-extern" "gnus/mm-extern.el" (20355 10021))
+;;;;;; "mm-extern" "gnus/mm-extern.el" (20244 35516))
;;; Generated autoloads from gnus/mm-extern.el
(autoload 'mm-extern-cache-contents "mm-extern" "\
;;;***
\f
;;;### (autoloads (mm-inline-partial) "mm-partial" "gnus/mm-partial.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/mm-partial.el
(autoload 'mm-inline-partial "mm-partial" "\
;;;***
\f
;;;### (autoloads (mm-url-insert-file-contents-external mm-url-insert-file-contents)
-;;;;;; "mm-url" "gnus/mm-url.el" (20355 10021))
+;;;;;; "mm-url" "gnus/mm-url.el" (20244 35516))
;;; Generated autoloads from gnus/mm-url.el
(autoload 'mm-url-insert-file-contents "mm-url" "\
;;;***
\f
;;;### (autoloads (mm-uu-dissect-text-parts mm-uu-dissect) "mm-uu"
-;;;;;; "gnus/mm-uu.el" (20355 10021))
+;;;;;; "gnus/mm-uu.el" (20318 5885))
;;; Generated autoloads from gnus/mm-uu.el
(autoload 'mm-uu-dissect "mm-uu" "\
;;;***
\f
;;;### (autoloads (mml-attach-file mml-to-mime) "mml" "gnus/mml.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/mml.el
(autoload 'mml-to-mime "mml" "\
;;;***
\f
;;;### (autoloads (mml1991-sign mml1991-encrypt) "mml1991" "gnus/mml1991.el"
-;;;;;; (20355 10021))
+;;;;;; (20291 57212))
;;; Generated autoloads from gnus/mml1991.el
(autoload 'mml1991-encrypt "mml1991" "\
\f
;;;### (autoloads (mml2015-self-encrypt mml2015-sign mml2015-encrypt
;;;;;; mml2015-verify-test mml2015-verify mml2015-decrypt-test mml2015-decrypt)
-;;;;;; "mml2015" "gnus/mml2015.el" (20355 10021))
+;;;;;; "mml2015" "gnus/mml2015.el" (20244 35516))
;;; Generated autoloads from gnus/mml2015.el
(autoload 'mml2015-decrypt "mml2015" "\
;;;***
\f
-;;;### (autoloads nil "mode-local" "cedet/mode-local.el" (20406 8611))
+;;;### (autoloads nil "mode-local" "cedet/mode-local.el" (20412 11425))
;;; Generated autoloads from cedet/mode-local.el
(put 'define-overloadable-function 'doc-string-elt 3)
;;;***
\f
-;;;### (autoloads (m2-mode) "modula2" "progmodes/modula2.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (m2-mode) "modula2" "progmodes/modula2.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from progmodes/modula2.el
(defalias 'modula-2-mode 'm2-mode)
;;;***
\f
;;;### (autoloads (denato-region nato-region unmorse-region morse-region)
-;;;;;; "morse" "play/morse.el" (20355 10021))
+;;;;;; "morse" "play/morse.el" (20244 35516))
;;; Generated autoloads from play/morse.el
(autoload 'morse-region "morse" "\
;;;***
\f
;;;### (autoloads (mouse-drag-drag mouse-drag-throw) "mouse-drag"
-;;;;;; "mouse-drag.el" (20355 10021))
+;;;;;; "mouse-drag.el" (20356 35090))
;;; Generated autoloads from mouse-drag.el
(autoload 'mouse-drag-throw "mouse-drag" "\
;;;***
\f
-;;;### (autoloads (mpc) "mpc" "mpc.el" (20378 29222))
+;;;### (autoloads (mpc) "mpc" "mpc.el" (20377 36640))
;;; Generated autoloads from mpc.el
(autoload 'mpc "mpc" "\
;;;***
\f
-;;;### (autoloads (mpuz) "mpuz" "play/mpuz.el" (20355 10021))
+;;;### (autoloads (mpuz) "mpuz" "play/mpuz.el" (20434 28080))
;;; Generated autoloads from play/mpuz.el
(autoload 'mpuz "mpuz" "\
;;;***
\f
-;;;### (autoloads (msb-mode) "msb" "msb.el" (20355 10021))
+;;;### (autoloads (msb-mode) "msb" "msb.el" (20356 35090))
;;; Generated autoloads from msb.el
(defvar msb-mode nil "\
;;;;;; describe-current-coding-system describe-current-coding-system-briefly
;;;;;; describe-coding-system describe-character-set list-charset-chars
;;;;;; read-charset list-character-sets) "mule-diag" "international/mule-diag.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from international/mule-diag.el
(autoload 'list-character-sets "mule-diag" "\
;;;;;; coding-system-translation-table-for-decode coding-system-pre-write-conversion
;;;;;; coding-system-post-read-conversion lookup-nested-alist set-nested-alist
;;;;;; truncate-string-to-width store-substring string-to-sequence)
-;;;;;; "mule-util" "international/mule-util.el" (20355 10021))
+;;;;;; "mule-util" "international/mule-util.el" (20244 35516))
;;; Generated autoloads from international/mule-util.el
(autoload 'string-to-sequence "mule-util" "\
This affects the implicit sorting of lists of coding systems returned by
operations such as `find-coding-systems-region'.
-\(fn CODING-SYSTEMS &rest BODY)" nil (quote macro))
+\(fn CODING-SYSTEMS &rest BODY)" nil t)
(put 'with-coding-priority 'lisp-indent-function 1)
(autoload 'detect-coding-with-priority "mule-util" "\
PRIORITY-LIST is an alist of coding categories vs the corresponding
coding systems ordered by priority.
-\(fn FROM TO PRIORITY-LIST)" nil (quote macro))
+\(fn FROM TO PRIORITY-LIST)" nil t)
(autoload 'detect-coding-with-language-environment "mule-util" "\
Detect a coding system for the text between FROM and TO with LANG-ENV.
;;;### (autoloads (network-connection network-connection-to-service
;;;;;; whois-reverse-lookup whois finger ftp run-dig dns-lookup-host
;;;;;; nslookup nslookup-host ping traceroute route arp netstat
-;;;;;; iwconfig ifconfig) "net-utils" "net/net-utils.el" (20355
-;;;;;; 10021))
+;;;;;; iwconfig ifconfig) "net-utils" "net/net-utils.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from net/net-utils.el
(autoload 'ifconfig "net-utils" "\
;;;***
\f
-;;;### (autoloads (netrc-credentials) "netrc" "net/netrc.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (netrc-credentials) "netrc" "net/netrc.el" (20290
+;;;;;; 33419))
;;; Generated autoloads from net/netrc.el
(autoload 'netrc-credentials "netrc" "\
;;;***
\f
;;;### (autoloads (open-network-stream) "network-stream" "net/network-stream.el"
-;;;;;; (20369 14251))
+;;;;;; (20373 41604))
;;; Generated autoloads from net/network-stream.el
(autoload 'open-network-stream "network-stream" "\
;;;***
\f
;;;### (autoloads (newsticker-start newsticker-running-p) "newst-backend"
-;;;;;; "net/newst-backend.el" (20355 10021))
+;;;;;; "net/newst-backend.el" (20244 35516))
;;; Generated autoloads from net/newst-backend.el
(autoload 'newsticker-running-p "newst-backend" "\
;;;***
\f
;;;### (autoloads (newsticker-plainview) "newst-plainview" "net/newst-plainview.el"
-;;;;;; (20355 10021))
+;;;;;; (20434 28080))
;;; Generated autoloads from net/newst-plainview.el
(autoload 'newsticker-plainview "newst-plainview" "\
;;;***
\f
;;;### (autoloads (newsticker-show-news) "newst-reader" "net/newst-reader.el"
-;;;;;; (20355 10021))
+;;;;;; (20434 28080))
;;; Generated autoloads from net/newst-reader.el
(autoload 'newsticker-show-news "newst-reader" "\
;;;***
\f
;;;### (autoloads (newsticker-start-ticker newsticker-ticker-running-p)
-;;;;;; "newst-ticker" "net/newst-ticker.el" (20355 10021))
+;;;;;; "newst-ticker" "net/newst-ticker.el" (20428 57510))
;;; Generated autoloads from net/newst-ticker.el
(autoload 'newsticker-ticker-running-p "newst-ticker" "\
;;;***
\f
;;;### (autoloads (newsticker-treeview) "newst-treeview" "net/newst-treeview.el"
-;;;;;; (20355 10021))
+;;;;;; (20434 28080))
;;; Generated autoloads from net/newst-treeview.el
(autoload 'newsticker-treeview "newst-treeview" "\
;;;***
\f
;;;### (autoloads (nndiary-generate-nov-databases) "nndiary" "gnus/nndiary.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/nndiary.el
(autoload 'nndiary-generate-nov-databases "nndiary" "\
;;;***
\f
-;;;### (autoloads (nndoc-add-type) "nndoc" "gnus/nndoc.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (nndoc-add-type) "nndoc" "gnus/nndoc.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from gnus/nndoc.el
(autoload 'nndoc-add-type "nndoc" "\
;;;***
\f
;;;### (autoloads (nnfolder-generate-active-file) "nnfolder" "gnus/nnfolder.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/nnfolder.el
(autoload 'nnfolder-generate-active-file "nnfolder" "\
;;;***
\f
;;;### (autoloads (nnml-generate-nov-databases) "nnml" "gnus/nnml.el"
-;;;;;; (20355 10021))
+;;;;;; (20290 33419))
;;; Generated autoloads from gnus/nnml.el
(autoload 'nnml-generate-nov-databases "nnml" "\
;;;***
\f
;;;### (autoloads (disable-command enable-command disabled-command-function)
-;;;;;; "novice" "novice.el" (20399 35365))
+;;;;;; "novice" "novice.el" (20412 11425))
;;; Generated autoloads from novice.el
(define-obsolete-variable-alias 'disabled-command-hook 'disabled-command-function "22.1")
;;;***
\f
;;;### (autoloads (nroff-mode) "nroff-mode" "textmodes/nroff-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from textmodes/nroff-mode.el
(autoload 'nroff-mode "nroff-mode" "\
;;;***
\f
;;;### (autoloads (nxml-glyph-display-string) "nxml-glyph" "nxml/nxml-glyph.el"
-;;;;;; (20355 10021))
+;;;;;; (20446 34252))
;;; Generated autoloads from nxml/nxml-glyph.el
(autoload 'nxml-glyph-display-string "nxml-glyph" "\
;;;***
\f
-;;;### (autoloads (nxml-mode) "nxml-mode" "nxml/nxml-mode.el" (20369
-;;;;;; 14251))
+;;;### (autoloads (nxml-mode) "nxml-mode" "nxml/nxml-mode.el" (20446
+;;;;;; 34252))
;;; Generated autoloads from nxml/nxml-mode.el
(autoload 'nxml-mode "nxml-mode" "\
;;;***
\f
;;;### (autoloads (nxml-enable-unicode-char-name-sets) "nxml-uchnm"
-;;;;;; "nxml/nxml-uchnm.el" (20355 10021))
+;;;;;; "nxml/nxml-uchnm.el" (20244 35516))
;;; Generated autoloads from nxml/nxml-uchnm.el
(autoload 'nxml-enable-unicode-char-name-sets "nxml-uchnm" "\
;;;;;; org-babel-pop-to-session-maybe org-babel-load-in-session-maybe
;;;;;; org-babel-expand-src-block-maybe org-babel-view-src-block-info
;;;;;; org-babel-execute-maybe org-babel-execute-safely-maybe) "ob"
-;;;;;; "org/ob.el" (20417 65331))
+;;;;;; "org/ob.el" (20419 46656))
;;; Generated autoloads from org/ob.el
(autoload 'org-babel-execute-safely-maybe "ob" "\
beg-body --------- point at the beginning of the body
end-body --------- point at the end of the body
-\(fn FILE &rest BODY)" nil (quote macro))
+\(fn FILE &rest BODY)" nil t)
(put 'org-babel-map-src-blocks 'lisp-indent-function '1)
If FILE is nil evaluate BODY forms on source blocks in current
buffer.
-\(fn FILE &rest BODY)" nil (quote macro))
+\(fn FILE &rest BODY)" nil t)
(put 'org-babel-map-inline-src-blocks 'lisp-indent-function '1)
If FILE is nil evaluate BODY forms on source blocks in current
buffer.
-\(fn FILE &rest BODY)" nil (quote macro))
+\(fn FILE &rest BODY)" nil t)
(put 'org-babel-map-call-lines 'lisp-indent-function '1)
(autoload 'org-babel-map-executables "ob" "\
-\(fn FILE &rest BODY)" nil (quote macro))
+\(fn FILE &rest BODY)" nil t)
(put 'org-babel-map-executables 'lisp-indent-function '1)
;;;***
\f
;;;### (autoloads (org-babel-describe-bindings) "ob-keys" "org/ob-keys.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from org/ob-keys.el
(autoload 'org-babel-describe-bindings "ob-keys" "\
;;;***
\f
;;;### (autoloads (org-babel-lob-get-info org-babel-lob-execute-maybe
-;;;;;; org-babel-lob-ingest) "ob-lob" "org/ob-lob.el" (20355 10021))
+;;;;;; org-babel-lob-ingest) "ob-lob" "org/ob-lob.el" (20356 19083))
;;; Generated autoloads from org/ob-lob.el
(autoload 'org-babel-lob-ingest "ob-lob" "\
\f
;;;### (autoloads (org-babel-tangle org-babel-tangle-file org-babel-load-file
;;;;;; org-babel-tangle-lang-exts) "ob-tangle" "org/ob-tangle.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 19083))
;;; Generated autoloads from org/ob-tangle.el
(defvar org-babel-tangle-lang-exts '(("emacs-lisp" . "el")) "\
;;;***
\f
;;;### (autoloads (inferior-octave) "octave-inf" "progmodes/octave-inf.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from progmodes/octave-inf.el
(autoload 'inferior-octave "octave-inf" "\
;;;***
\f
;;;### (autoloads (octave-mode) "octave-mod" "progmodes/octave-mod.el"
-;;;;;; (20388 65061))
+;;;;;; (20412 11425))
;;; Generated autoloads from progmodes/octave-mod.el
(autoload 'octave-mode "octave-mod" "\
;;;;;; org-insert-link-global org-store-link org-run-like-in-org-mode
;;;;;; turn-on-orgstruct++ turn-on-orgstruct orgstruct-mode org-global-cycle
;;;;;; org-mode org-version org-babel-do-load-languages) "org" "org/org.el"
-;;;;;; (20420 41510))
+;;;;;; (20420 52684))
;;; Generated autoloads from org/org.el
(autoload 'org-babel-do-load-languages "org" "\
;;;;;; org-diary org-agenda-list-stuck-projects org-tags-view org-todo-list
;;;;;; org-search-view org-agenda-list org-batch-store-agenda-views
;;;;;; org-store-agenda-views org-batch-agenda-csv org-batch-agenda
-;;;;;; org-agenda) "org-agenda" "org/org-agenda.el" (20420 41510))
+;;;;;; org-agenda) "org-agenda" "org/org-agenda.el" (20420 52684))
;;; Generated autoloads from org/org-agenda.el
(autoload 'org-agenda "org-agenda" "\
Parameters are alternating variable names and values that will be bound
before running the agenda command.
-\(fn CMD-KEY &rest PARAMETERS)" nil (quote macro))
+\(fn CMD-KEY &rest PARAMETERS)" nil t)
(autoload 'org-batch-agenda-csv "org-agenda" "\
Run an agenda command in batch mode and send the result to STDOUT.
priority-n The computed numerical priority
agenda-day The day in the agenda where this is listed
-\(fn CMD-KEY &rest PARAMETERS)" nil (quote macro))
+\(fn CMD-KEY &rest PARAMETERS)" nil t)
(autoload 'org-store-agenda-views "org-agenda" "\
(autoload 'org-batch-store-agenda-views "org-agenda" "\
Run all custom agenda commands that have a file argument.
-\(fn &rest PARAMETERS)" nil (quote macro))
+\(fn &rest PARAMETERS)" nil t)
(autoload 'org-agenda-list "org-agenda" "\
Produce a daily/weekly view from all files in variable `org-agenda-files'.
\f
;;;### (autoloads (org-archive-subtree-default-with-confirmation
;;;;;; org-archive-subtree-default) "org-archive" "org/org-archive.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 19083))
;;; Generated autoloads from org/org-archive.el
(autoload 'org-archive-subtree-default "org-archive" "\
;;;### (autoloads (org-export-as-ascii org-export-region-as-ascii
;;;;;; org-replace-region-by-ascii org-export-as-ascii-to-buffer
;;;;;; org-export-as-utf8-to-buffer org-export-as-utf8 org-export-as-latin1-to-buffer
-;;;;;; org-export-as-latin1) "org-ascii" "org/org-ascii.el" (20355
-;;;;;; 10021))
+;;;;;; org-export-as-latin1) "org-ascii" "org/org-ascii.el" (20345
+;;;;;; 61951))
;;; Generated autoloads from org/org-ascii.el
(autoload 'org-export-as-latin1 "org-ascii" "\
;;;***
\f
-;;;### (autoloads (org-attach) "org-attach" "org/org-attach.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (org-attach) "org-attach" "org/org-attach.el" (20356
+;;;;;; 19083))
;;; Generated autoloads from org/org-attach.el
(autoload 'org-attach "org-attach" "\
;;;***
\f
;;;### (autoloads (org-bbdb-anniversaries) "org-bbdb" "org/org-bbdb.el"
-;;;;;; (20355 10021))
+;;;;;; (20345 61951))
;;; Generated autoloads from org/org-bbdb.el
(autoload 'org-bbdb-anniversaries "org-bbdb" "\
;;;***
\f
;;;### (autoloads (org-capture-import-remember-templates org-capture-insert-template-here
-;;;;;; org-capture) "org-capture" "org/org-capture.el" (20355 10021))
+;;;;;; org-capture) "org-capture" "org/org-capture.el" (20356 19083))
;;; Generated autoloads from org/org-capture.el
(autoload 'org-capture "org-capture" "\
;;;***
\f
;;;### (autoloads (org-clock-persistence-insinuate org-get-clocktable)
-;;;;;; "org-clock" "org/org-clock.el" (20378 29222))
+;;;;;; "org-clock" "org/org-clock.el" (20428 57510))
;;; Generated autoloads from org/org-clock.el
(autoload 'org-get-clocktable "org-clock" "\
;;;***
\f
;;;### (autoloads (org-datetree-find-date-create) "org-datetree"
-;;;;;; "org/org-datetree.el" (20355 10021))
+;;;;;; "org/org-datetree.el" (20345 61951))
;;; Generated autoloads from org/org-datetree.el
(autoload 'org-datetree-find-date-create "org-datetree" "\
;;;### (autoloads (org-export-as-docbook org-export-as-docbook-pdf-and-open
;;;;;; org-export-as-docbook-pdf org-export-region-as-docbook org-replace-region-by-docbook
;;;;;; org-export-as-docbook-to-buffer org-export-as-docbook-batch)
-;;;;;; "org-docbook" "org/org-docbook.el" (20355 10021))
+;;;;;; "org-docbook" "org/org-docbook.el" (20356 19083))
;;; Generated autoloads from org/org-docbook.el
(autoload 'org-export-as-docbook-batch "org-docbook" "\
\f
;;;### (autoloads (org-insert-export-options-template org-export-as-org
;;;;;; org-export-visible org-export) "org-exp" "org/org-exp.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 19083))
;;; Generated autoloads from org/org-exp.el
(autoload 'org-export "org-exp" "\
;;;***
\f
;;;### (autoloads (org-feed-show-raw-feed org-feed-goto-inbox org-feed-update
-;;;;;; org-feed-update-all) "org-feed" "org/org-feed.el" (20355
-;;;;;; 10021))
+;;;;;; org-feed-update-all) "org-feed" "org/org-feed.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from org/org-feed.el
(autoload 'org-feed-update-all "org-feed" "\
;;;***
\f
;;;### (autoloads (org-footnote-normalize org-footnote-action) "org-footnote"
-;;;;;; "org/org-footnote.el" (20378 29222))
+;;;;;; "org/org-footnote.el" (20380 26775))
;;; Generated autoloads from org/org-footnote.el
(autoload 'org-footnote-action "org-footnote" "\
;;;### (autoloads (org-freemind-to-org-mode org-freemind-from-org-sparse-tree
;;;;;; org-freemind-from-org-mode org-freemind-from-org-mode-node
;;;;;; org-freemind-show org-export-as-freemind) "org-freemind"
-;;;;;; "org/org-freemind.el" (20355 10021))
+;;;;;; "org/org-freemind.el" (20356 19083))
;;; Generated autoloads from org/org-freemind.el
(autoload 'org-export-as-freemind "org-freemind" "\
;;;### (autoloads (org-export-htmlize-generate-css org-export-as-html
;;;;;; org-export-region-as-html org-replace-region-by-html org-export-as-html-to-buffer
;;;;;; org-export-as-html-batch org-export-as-html-and-open) "org-html"
-;;;;;; "org/org-html.el" (20355 10021))
+;;;;;; "org/org-html.el" (20356 19083))
;;; Generated autoloads from org/org-html.el
(put 'org-export-html-style-include-default 'safe-local-variable 'booleanp)
\f
;;;### (autoloads (org-export-icalendar-combine-agenda-files org-export-icalendar-all-agenda-files
;;;;;; org-export-icalendar-this-file) "org-icalendar" "org/org-icalendar.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 19083))
;;; Generated autoloads from org/org-icalendar.el
(autoload 'org-export-icalendar-this-file "org-icalendar" "\
;;;### (autoloads (org-id-store-link org-id-find-id-file org-id-find
;;;;;; org-id-goto org-id-get-with-outline-drilling org-id-get-with-outline-path-completion
;;;;;; org-id-get org-id-copy org-id-get-create) "org-id" "org/org-id.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from org/org-id.el
(autoload 'org-id-get-create "org-id" "\
;;;***
\f
;;;### (autoloads (org-indent-mode) "org-indent" "org/org-indent.el"
-;;;;;; (20355 10021))
+;;;;;; (20345 61951))
;;; Generated autoloads from org/org-indent.el
(autoload 'org-indent-mode "org-indent" "\
;;;***
\f
;;;### (autoloads (org-irc-store-link) "org-irc" "org/org-irc.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from org/org-irc.el
(autoload 'org-irc-store-link "org-irc" "\
;;;### (autoloads (org-export-as-pdf-and-open org-export-as-pdf org-export-as-latex
;;;;;; org-export-region-as-latex org-replace-region-by-latex org-export-as-latex-to-buffer
;;;;;; org-export-as-latex-batch) "org-latex" "org/org-latex.el"
-;;;;;; (20355 10021))
+;;;;;; (20345 61951))
;;; Generated autoloads from org/org-latex.el
(autoload 'org-export-as-latex-batch "org-latex" "\
\f
;;;### (autoloads (org-lparse-region org-replace-region-by org-lparse-to-buffer
;;;;;; org-lparse-batch org-lparse-and-open) "org-lparse" "org/org-lparse.el"
-;;;;;; (20417 65331))
+;;;;;; (20419 46656))
;;; Generated autoloads from org/org-lparse.el
(autoload 'org-lparse-and-open "org-lparse" "\
;;;***
\f
;;;### (autoloads (org-mobile-create-sumo-agenda org-mobile-pull
-;;;;;; org-mobile-push) "org-mobile" "org/org-mobile.el" (20355
-;;;;;; 10021))
+;;;;;; org-mobile-push) "org-mobile" "org/org-mobile.el" (20356
+;;;;;; 19083))
;;; Generated autoloads from org/org-mobile.el
(autoload 'org-mobile-push "org-mobile" "\
\f
;;;### (autoloads (org-export-as-odf-and-open org-export-as-odf org-export-odt-convert
;;;;;; org-export-as-odt org-export-as-odt-batch org-export-as-odt-and-open)
-;;;;;; "org-odt" "org/org-odt.el" (20417 65331))
+;;;;;; "org-odt" "org/org-odt.el" (20419 46656))
;;; Generated autoloads from org/org-odt.el
(autoload 'org-export-as-odt-and-open "org-odt" "\
;;;***
\f
;;;### (autoloads (org-plot/gnuplot) "org-plot" "org/org-plot.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from org/org-plot.el
(autoload 'org-plot/gnuplot "org-plot" "\
\f
;;;### (autoloads (org-publish-current-project org-publish-current-file
;;;;;; org-publish-all org-publish) "org-publish" "org/org-publish.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 19083))
;;; Generated autoloads from org/org-publish.el
(defalias 'org-publish-project 'org-publish)
\f
;;;### (autoloads (org-remember-handler org-remember org-remember-apply-template
;;;;;; org-remember-annotation org-remember-insinuate) "org-remember"
-;;;;;; "org/org-remember.el" (20420 41510))
+;;;;;; "org/org-remember.el" (20420 52684))
;;; Generated autoloads from org/org-remember.el
(autoload 'org-remember-insinuate "org-remember" "\
;;;***
\f
;;;### (autoloads (org-table-to-lisp orgtbl-mode turn-on-orgtbl)
-;;;;;; "org-table" "org/org-table.el" (20417 65331))
+;;;;;; "org-table" "org/org-table.el" (20419 46656))
;;; Generated autoloads from org/org-table.el
(autoload 'turn-on-orgtbl "org-table" "\
;;;***
\f
;;;### (autoloads (org-export-as-taskjuggler-and-open org-export-as-taskjuggler)
-;;;;;; "org-taskjuggler" "org/org-taskjuggler.el" (20355 10021))
+;;;;;; "org-taskjuggler" "org/org-taskjuggler.el" (20356 19083))
;;; Generated autoloads from org/org-taskjuggler.el
(autoload 'org-export-as-taskjuggler "org-taskjuggler" "\
\f
;;;### (autoloads (org-timer-set-timer org-timer-item org-timer-change-times-in-region
;;;;;; org-timer org-timer-start) "org-timer" "org/org-timer.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 19083))
;;; Generated autoloads from org/org-timer.el
(autoload 'org-timer-start "org-timer" "\
;;;***
\f
;;;### (autoloads (org-export-as-xoxo) "org-xoxo" "org/org-xoxo.el"
-;;;;;; (20355 10021))
+;;;;;; (20345 61951))
;;; Generated autoloads from org/org-xoxo.el
(autoload 'org-export-as-xoxo "org-xoxo" "\
;;;***
\f
;;;### (autoloads (outline-minor-mode outline-mode) "outline" "outline.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from outline.el
(put 'outline-regexp 'safe-local-variable 'stringp)
(put 'outline-heading-end-regexp 'safe-local-variable 'stringp)
;;;### (autoloads (list-packages describe-package package-initialize
;;;;;; package-refresh-contents package-install-file package-install-from-buffer
;;;;;; package-install package-enable-at-startup) "package" "emacs-lisp/package.el"
-;;;;;; (20394 17446))
+;;;;;; (20446 34252))
;;; Generated autoloads from emacs-lisp/package.el
(defvar package-enable-at-startup t "\
;;;***
\f
-;;;### (autoloads (show-paren-mode) "paren" "paren.el" (20355 10021))
+;;;### (autoloads (show-paren-mode) "paren" "paren.el" (20356 35090))
;;; Generated autoloads from paren.el
(defvar show-paren-mode nil "\
;;;***
\f
;;;### (autoloads (parse-time-string) "parse-time" "calendar/parse-time.el"
-;;;;;; (20355 10021))
+;;;;;; (20318 5885))
;;; Generated autoloads from calendar/parse-time.el
(put 'parse-time-rules 'risky-local-variable t)
;;;***
\f
-;;;### (autoloads (pascal-mode) "pascal" "progmodes/pascal.el" (20378
-;;;;;; 29222))
+;;;### (autoloads (pascal-mode) "pascal" "progmodes/pascal.el" (20446
+;;;;;; 34252))
;;; Generated autoloads from progmodes/pascal.el
(autoload 'pascal-mode "pascal" "\
;;;***
\f
;;;### (autoloads (password-in-cache-p password-cache-expiry password-cache)
-;;;;;; "password-cache" "password-cache.el" (20355 10021))
+;;;;;; "password-cache" "password-cache.el" (20244 35516))
;;; Generated autoloads from password-cache.el
(defvar password-cache t "\
;;;***
\f
;;;### (autoloads (pcase-let pcase-let* pcase) "pcase" "emacs-lisp/pcase.el"
-;;;;;; (20421 62373))
+;;;;;; (20451 34853))
;;; Generated autoloads from emacs-lisp/pcase.el
(autoload 'pcase "pcase" "\
like `(,a . ,(pred (< a))) or, with more checks:
`(,(and a (pred numberp)) . ,(and (pred numberp) (pred (< a))))
-\(fn EXP &rest CASES)" nil (quote macro))
+\(fn EXP &rest CASES)" nil t)
(put 'pcase 'lisp-indent-function '1)
BODY should be an expression, and BINDINGS should be a list of bindings
of the form (UPAT EXP).
-\(fn BINDINGS &rest BODY)" nil (quote macro))
+\(fn BINDINGS &rest BODY)" nil t)
(put 'pcase-let* 'lisp-indent-function '1)
BODY should be a list of expressions, and BINDINGS should be a list of bindings
of the form (UPAT EXP).
-\(fn BINDINGS &rest BODY)" nil (quote macro))
+\(fn BINDINGS &rest BODY)" nil t)
(put 'pcase-let 'lisp-indent-function '1)
;;;***
\f
-;;;### (autoloads (pcomplete/cvs) "pcmpl-cvs" "pcmpl-cvs.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (pcomplete/cvs) "pcmpl-cvs" "pcmpl-cvs.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from pcmpl-cvs.el
(autoload 'pcomplete/cvs "pcmpl-cvs" "\
;;;***
\f
;;;### (autoloads (pcomplete/tar pcomplete/make pcomplete/bzip2 pcomplete/gzip)
-;;;;;; "pcmpl-gnu" "pcmpl-gnu.el" (20355 10021))
+;;;;;; "pcmpl-gnu" "pcmpl-gnu.el" (20276 3849))
;;; Generated autoloads from pcmpl-gnu.el
(autoload 'pcomplete/gzip "pcmpl-gnu" "\
;;;***
\f
;;;### (autoloads (pcomplete/mount pcomplete/umount pcomplete/kill)
-;;;;;; "pcmpl-linux" "pcmpl-linux.el" (20355 10021))
+;;;;;; "pcmpl-linux" "pcmpl-linux.el" (20244 35516))
;;; Generated autoloads from pcmpl-linux.el
(autoload 'pcomplete/kill "pcmpl-linux" "\
;;;***
\f
-;;;### (autoloads (pcomplete/rpm) "pcmpl-rpm" "pcmpl-rpm.el" (20361
-;;;;;; 20134))
+;;;### (autoloads (pcomplete/rpm) "pcmpl-rpm" "pcmpl-rpm.el" (20373
+;;;;;; 41604))
;;; Generated autoloads from pcmpl-rpm.el
(autoload 'pcomplete/rpm "pcmpl-rpm" "\
\f
;;;### (autoloads (pcomplete/scp pcomplete/ssh pcomplete/chgrp pcomplete/chown
;;;;;; pcomplete/which pcomplete/xargs pcomplete/rm pcomplete/rmdir
-;;;;;; pcomplete/cd) "pcmpl-unix" "pcmpl-unix.el" (20376 40834))
+;;;;;; pcomplete/cd) "pcmpl-unix" "pcmpl-unix.el" (20375 3831))
;;; Generated autoloads from pcmpl-unix.el
(autoload 'pcomplete/cd "pcmpl-unix" "\
\f
;;;### (autoloads (pcomplete-shell-setup pcomplete-comint-setup pcomplete-list
;;;;;; pcomplete-help pcomplete-expand pcomplete-continue pcomplete-expand-and-complete
-;;;;;; pcomplete-reverse pcomplete) "pcomplete" "pcomplete.el" (20376
-;;;;;; 40834))
+;;;;;; pcomplete-reverse pcomplete) "pcomplete" "pcomplete.el" (20377
+;;;;;; 36816))
;;; Generated autoloads from pcomplete.el
(autoload 'pcomplete "pcomplete" "\
\f
;;;### (autoloads (cvs-dired-use-hook cvs-dired-action cvs-status
;;;;;; cvs-update cvs-examine cvs-quickdir cvs-checkout) "pcvs"
-;;;;;; "vc/pcvs.el" (20364 45187))
+;;;;;; "vc/pcvs.el" (20373 41604))
;;; Generated autoloads from vc/pcvs.el
(autoload 'cvs-checkout "pcvs" "\
;;;***
\f
-;;;### (autoloads nil "pcvs-defs" "vc/pcvs-defs.el" (20355 10021))
+;;;### (autoloads nil "pcvs-defs" "vc/pcvs-defs.el" (20356 35090))
;;; Generated autoloads from vc/pcvs-defs.el
(defvar cvs-global-menu (let ((m (make-sparse-keymap "PCL-CVS"))) (define-key m [status] `(menu-item ,(purecopy "Directory Status") cvs-status :help ,(purecopy "A more verbose status of a workarea"))) (define-key m [checkout] `(menu-item ,(purecopy "Checkout Module") cvs-checkout :help ,(purecopy "Check out a module from the repository"))) (define-key m [update] `(menu-item ,(purecopy "Update Directory") cvs-update :help ,(purecopy "Fetch updates from the repository"))) (define-key m [examine] `(menu-item ,(purecopy "Examine Directory") cvs-examine :help ,(purecopy "Examine the current state of a workarea"))) (fset 'cvs-global-menu m)) "\
;;;***
\f
;;;### (autoloads (perl-mode) "perl-mode" "progmodes/perl-mode.el"
-;;;;;; (20365 17199))
+;;;;;; (20373 41604))
;;; Generated autoloads from progmodes/perl-mode.el
(put 'perl-indent-level 'safe-local-variable 'integerp)
(put 'perl-continued-statement-offset 'safe-local-variable 'integerp)
;;;***
\f
;;;### (autoloads (picture-mode) "picture" "textmodes/picture.el"
-;;;;;; (20373 11301))
+;;;;;; (20373 41604))
;;; Generated autoloads from textmodes/picture.el
(autoload 'picture-mode "picture" "\
;;;***
\f
;;;### (autoloads (plstore-mode plstore-open) "plstore" "gnus/plstore.el"
-;;;;;; (20378 29222))
+;;;;;; (20380 26775))
;;; Generated autoloads from gnus/plstore.el
(autoload 'plstore-open "plstore" "\
;;;***
\f
;;;### (autoloads (po-find-file-coding-system) "po" "textmodes/po.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from textmodes/po.el
(autoload 'po-find-file-coding-system "po" "\
;;;***
\f
-;;;### (autoloads (pong) "pong" "play/pong.el" (20355 10021))
+;;;### (autoloads (pong) "pong" "play/pong.el" (20244 35516))
;;; Generated autoloads from play/pong.el
(autoload 'pong "pong" "\
;;;***
\f
-;;;### (autoloads (pop3-movemail) "pop3" "gnus/pop3.el" (20355 10021))
+;;;### (autoloads (pop3-movemail) "pop3" "gnus/pop3.el" (20244 35516))
;;; Generated autoloads from gnus/pop3.el
(autoload 'pop3-movemail "pop3" "\
\f
;;;### (autoloads (pp-macroexpand-last-sexp pp-eval-last-sexp pp-macroexpand-expression
;;;;;; pp-eval-expression pp pp-buffer pp-to-string) "pp" "emacs-lisp/pp.el"
-;;;;;; (20355 10021))
+;;;;;; (20276 3849))
;;; Generated autoloads from emacs-lisp/pp.el
(autoload 'pp-to-string "pp" "\
;;;;;; pr-ps-buffer-print pr-ps-buffer-using-ghostscript pr-ps-buffer-preview
;;;;;; pr-ps-directory-ps-print pr-ps-directory-print pr-ps-directory-using-ghostscript
;;;;;; pr-ps-directory-preview pr-interface) "printing" "printing.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from printing.el
(autoload 'pr-interface "printing" "\
;;;***
\f
-;;;### (autoloads (proced) "proced" "proced.el" (20355 10021))
+;;;### (autoloads (proced) "proced" "proced.el" (20428 57510))
;;; Generated autoloads from proced.el
(autoload 'proced "proced" "\
;;;***
\f
;;;### (autoloads (run-prolog mercury-mode prolog-mode) "prolog"
-;;;;;; "progmodes/prolog.el" (20397 45851))
+;;;;;; "progmodes/prolog.el" (20412 11425))
;;; Generated autoloads from progmodes/prolog.el
(autoload 'prolog-mode "prolog" "\
;;;***
\f
-;;;### (autoloads (bdf-directory-list) "ps-bdf" "ps-bdf.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (bdf-directory-list) "ps-bdf" "ps-bdf.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from ps-bdf.el
(defvar bdf-directory-list (if (memq system-type '(ms-dos windows-nt)) (list (expand-file-name "fonts/bdf" installation-directory)) '("/usr/local/share/emacs/fonts/bdf")) "\
;;;***
\f
-;;;### (autoloads (ps-mode) "ps-mode" "progmodes/ps-mode.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (ps-mode) "ps-mode" "progmodes/ps-mode.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from progmodes/ps-mode.el
(autoload 'ps-mode "ps-mode" "\
;;;;;; ps-spool-region ps-spool-buffer-with-faces ps-spool-buffer
;;;;;; ps-print-region-with-faces ps-print-region ps-print-buffer-with-faces
;;;;;; ps-print-buffer ps-print-customize ps-print-color-p ps-paper-type
-;;;;;; ps-page-dimensions-database) "ps-print" "ps-print.el" (20355
-;;;;;; 10021))
+;;;;;; ps-page-dimensions-database) "ps-print" "ps-print.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from ps-print.el
(defvar ps-page-dimensions-database (purecopy (list (list 'a4 (/ (* 72 21.0) 2.54) (/ (* 72 29.7) 2.54) "A4") (list 'a3 (/ (* 72 29.7) 2.54) (/ (* 72 42.0) 2.54) "A3") (list 'letter (* 72 8.5) (* 72 11.0) "Letter") (list 'legal (* 72 8.5) (* 72 14.0) "Legal") (list 'letter-small (* 72 7.68) (* 72 10.16) "LetterSmall") (list 'tabloid (* 72 11.0) (* 72 17.0) "Tabloid") (list 'ledger (* 72 17.0) (* 72 11.0) "Ledger") (list 'statement (* 72 5.5) (* 72 8.5) "Statement") (list 'executive (* 72 7.5) (* 72 10.0) "Executive") (list 'a4small (* 72 7.47) (* 72 10.85) "A4Small") (list 'b4 (* 72 10.125) (* 72 14.33) "B4") (list 'b5 (* 72 7.16) (* 72 10.125) "B5") '(addresslarge 236.0 99.0 "AddressLarge") '(addresssmall 236.0 68.0 "AddressSmall") '(cuthanging13 90.0 222.0 "CutHanging13") '(cuthanging15 90.0 114.0 "CutHanging15") '(diskette 181.0 136.0 "Diskette") '(eurofilefolder 139.0 112.0 "EuropeanFilefolder") '(eurofoldernarrow 526.0 107.0 "EuroFolderNarrow") '(eurofolderwide 526.0 136.0 "EuroFolderWide") '(euronamebadge 189.0 108.0 "EuroNameBadge") '(euronamebadgelarge 223.0 136.0 "EuroNameBadgeLarge") '(filefolder 230.0 37.0 "FileFolder") '(jewelry 76.0 136.0 "Jewelry") '(mediabadge 180.0 136.0 "MediaBadge") '(multipurpose 126.0 68.0 "MultiPurpose") '(retaillabel 90.0 104.0 "RetailLabel") '(shipping 271.0 136.0 "Shipping") '(slide35mm 26.0 104.0 "Slide35mm") '(spine8mm 187.0 26.0 "Spine8mm") '(topcoated 425.19685 136.0 "TopCoatedPaper") '(topcoatedpaper 396.0 136.0 "TopcoatedPaper150") '(vhsface 205.0 127.0 "VHSFace") '(vhsspine 400.0 50.0 "VHSSpine") '(zipdisk 156.0 136.0 "ZipDisk"))) "\
;;;***
\f
-;;;### (autoloads (jython-mode python-mode python-after-info-look
-;;;;;; run-python) "python" "progmodes/python.el" (20376 40834))
+;;;### (autoloads (python-mode) "python" "progmodes/python.el" (20448
+;;;;;; 45252))
;;; Generated autoloads from progmodes/python.el
-(add-to-list 'interpreter-mode-alist (cons (purecopy "jython") 'jython-mode))
-
-(add-to-list 'interpreter-mode-alist (cons (purecopy "python") 'python-mode))
-
(add-to-list 'auto-mode-alist (cons (purecopy "\\.py\\'") 'python-mode))
-(autoload 'run-python "python" "\
-Run an inferior Python process, input and output via buffer *Python*.
-CMD is the Python command to run. NOSHOW non-nil means don't
-show the buffer automatically.
-
-Interactively, a prefix arg means to prompt for the initial
-Python command line (default is `python-command').
-
-A new process is started if one isn't running attached to
-`python-buffer', or if called from Lisp with non-nil arg NEW.
-Otherwise, if a process is already running in `python-buffer',
-switch to that buffer.
-
-This command runs the hook `inferior-python-mode-hook' after
-running `comint-mode-hook'. Type \\[describe-mode] in the
-process buffer for a list of commands.
-
-By default, Emacs inhibits the loading of Python modules from the
-current working directory, for security reasons. To disable this
-behavior, change `python-remove-cwd-from-path' to nil.
-
-\(fn &optional CMD NOSHOW NEW)" t nil)
-
-(autoload 'python-after-info-look "python" "\
-Set up info-look for Python.
-Used with `eval-after-load'.
-
-\(fn)" nil nil)
+(add-to-list 'interpreter-mode-alist (cons (purecopy "python") 'python-mode))
(autoload 'python-mode "python" "\
Major mode for editing Python files.
-Turns on Font Lock mode unconditionally since it is currently required
-for correct parsing of the source.
-See also `jython-mode', which is actually invoked if the buffer appears to
-contain Jython code. See also `run-python' and associated Python mode
-commands for running Python under Emacs.
-
-The Emacs commands which work with `defun's, e.g. \\[beginning-of-defun], deal
-with nested `def' and `class' blocks. They take the innermost one as
-current without distinguishing method and class definitions. Used multiple
-times, they move over others at the same indentation level until they reach
-the end of definitions at that level, when they move up a level.
-\\<python-mode-map>
-Colon is electric: it outdents the line if appropriate, e.g. for
-an else statement. \\[python-backspace] at the beginning of an indented statement
-deletes a level of indentation to close the current block; otherwise it
-deletes a character backward. TAB indents the current line relative to
-the preceding code. Successive TABs, with no intervening command, cycle
-through the possibilities for indentation on the basis of enclosing blocks.
-
-\\[fill-paragraph] fills comments and multi-line strings appropriately, but has no
-effect outside them.
-
-Supports Eldoc mode (only for functions, using a Python process),
-Info-Look and Imenu. In Outline minor mode, `class' and `def'
-lines count as headers. Symbol completion is available in the
-same way as in the Python shell using the `rlcompleter' module
-and this is added to the Hippie Expand functions locally if
-Hippie Expand mode is turned on. Completion of symbols of the
-form x.y only works if the components are literal
-module/attribute names, not variables. An abbrev table is set up
-with skeleton expansions for compound statement templates.
\\{python-mode-map}
-
-\(fn)" t nil)
-
-(autoload 'jython-mode "python" "\
-Major mode for editing Jython files.
-Like `python-mode', but sets up parameters for Jython subprocesses.
-Runs `jython-mode-hook' after `python-mode-hook'.
+Entry to this mode calls the value of `python-mode-hook'
+if that value is non-nil.
\(fn)" t nil)
;;;***
\f
;;;### (autoloads (quoted-printable-decode-region) "qp" "gnus/qp.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/qp.el
(autoload 'quoted-printable-decode-region "qp" "\
;;;;;; quail-defrule quail-install-decode-map quail-install-map
;;;;;; quail-define-rules quail-show-keyboard-layout quail-set-keyboard-layout
;;;;;; quail-define-package quail-use-package quail-title) "quail"
-;;;;;; "international/quail.el" (20356 55829))
+;;;;;; "international/quail.el" (20331 16635))
;;; Generated autoloads from international/quail.el
(autoload 'quail-title "quail" "\
no-decode-map --- the value non-nil means that decoding map is not
generated for the following translations.
-\(fn &rest RULES)" nil (quote macro))
+\(fn &rest RULES)" nil t)
(autoload 'quail-install-map "quail" "\
Install the Quail map MAP in the current Quail package.
\f
;;;### (autoloads (quickurl-list quickurl-list-mode quickurl-edit-urls
;;;;;; quickurl-browse-url-ask quickurl-browse-url quickurl-add-url
-;;;;;; quickurl-ask quickurl) "quickurl" "net/quickurl.el" (20355
-;;;;;; 10021))
+;;;;;; quickurl-ask) "quickurl" "net/quickurl.el" (20356 35090))
;;; Generated autoloads from net/quickurl.el
(defconst quickurl-reread-hook-postfix "\n;; Local Variables:\n;; eval: (progn (require 'quickurl) (add-hook 'local-write-file-hooks (lambda () (quickurl-read) nil)))\n;; End:\n" "\
in your ~/.emacs (after loading/requiring quickurl).")
-(autoload 'quickurl "quickurl" "\
-Insert a URL based on LOOKUP.
-
-If not supplied LOOKUP is taken to be the word at point in the current
-buffer, this default action can be modified via
-`quickurl-grab-lookup-function'.
-
-\(fn &optional LOOKUP)" t nil)
-
(autoload 'quickurl-ask "quickurl" "\
Insert a URL, with `completing-read' prompt, based on LOOKUP.
;;;***
\f
;;;### (autoloads (rcirc-track-minor-mode rcirc-connect rcirc) "rcirc"
-;;;;;; "net/rcirc.el" (20371 55972))
+;;;;;; "net/rcirc.el" (20434 28080))
;;; Generated autoloads from net/rcirc.el
(autoload 'rcirc "rcirc" "\
;;;***
\f
-;;;### (autoloads (remote-compile) "rcompile" "net/rcompile.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (remote-compile) "rcompile" "net/rcompile.el" (20290
+;;;;;; 33419))
;;; Generated autoloads from net/rcompile.el
(autoload 'remote-compile "rcompile" "\
;;;***
\f
;;;### (autoloads (re-builder) "re-builder" "emacs-lisp/re-builder.el"
-;;;;;; (20355 10021))
+;;;;;; (20428 57510))
;;; Generated autoloads from emacs-lisp/re-builder.el
(defalias 'regexp-builder 're-builder)
;;;***
\f
-;;;### (autoloads (recentf-mode) "recentf" "recentf.el" (20356 2211))
+;;;### (autoloads (recentf-mode) "recentf" "recentf.el" (20356 35090))
;;; Generated autoloads from recentf.el
(defvar recentf-mode nil "\
;;;;;; string-rectangle delete-whitespace-rectangle open-rectangle
;;;;;; insert-rectangle yank-rectangle kill-rectangle extract-rectangle
;;;;;; delete-extract-rectangle delete-rectangle) "rect" "rect.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from rect.el
(define-key ctl-x-r-map "c" 'clear-rectangle)
(define-key ctl-x-r-map "k" 'kill-rectangle)
;;;***
\f
-;;;### (autoloads (refill-mode) "refill" "textmodes/refill.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (refill-mode) "refill" "textmodes/refill.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from textmodes/refill.el
(autoload 'refill-mode "refill" "\
;;;***
\f
;;;### (autoloads (reftex-reset-scanning-information reftex-mode
-;;;;;; turn-on-reftex) "reftex" "textmodes/reftex.el" (20355 10021))
+;;;;;; turn-on-reftex) "reftex" "textmodes/reftex.el" (20244 35516))
;;; Generated autoloads from textmodes/reftex.el
(autoload 'turn-on-reftex "reftex" "\
;;;***
\f
;;;### (autoloads (reftex-citation) "reftex-cite" "textmodes/reftex-cite.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from textmodes/reftex-cite.el
(autoload 'reftex-citation "reftex-cite" "\
;;;***
\f
;;;### (autoloads (reftex-isearch-minor-mode) "reftex-global" "textmodes/reftex-global.el"
-;;;;;; (20420 41510))
+;;;;;; (20428 57510))
;;; Generated autoloads from textmodes/reftex-global.el
(autoload 'reftex-isearch-minor-mode "reftex-global" "\
;;;***
\f
;;;### (autoloads (reftex-index-phrases-mode) "reftex-index" "textmodes/reftex-index.el"
-;;;;;; (20399 35365))
+;;;;;; (20412 11425))
;;; Generated autoloads from textmodes/reftex-index.el
(autoload 'reftex-index-phrases-mode "reftex-index" "\
;;;***
\f
;;;### (autoloads (reftex-all-document-files) "reftex-parse" "textmodes/reftex-parse.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from textmodes/reftex-parse.el
(autoload 'reftex-all-document-files "reftex-parse" "\
;;;***
\f
-;;;### (autoloads nil "reftex-vars" "textmodes/reftex-vars.el" (20355
-;;;;;; 10021))
+;;;### (autoloads nil "reftex-vars" "textmodes/reftex-vars.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from textmodes/reftex-vars.el
(put 'reftex-vref-is-default 'safe-local-variable (lambda (x) (or (stringp x) (symbolp x))))
(put 'reftex-fref-is-default 'safe-local-variable (lambda (x) (or (stringp x) (symbolp x))))
;;;***
\f
;;;### (autoloads (regexp-opt-depth regexp-opt) "regexp-opt" "emacs-lisp/regexp-opt.el"
-;;;;;; (20363 61861))
+;;;;;; (20373 41604))
;;; Generated autoloads from emacs-lisp/regexp-opt.el
(autoload 'regexp-opt "regexp-opt" "\
\f
;;;### (autoloads (remember-diary-extract-entries remember-clipboard
;;;;;; remember-other-frame remember) "remember" "textmodes/remember.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from textmodes/remember.el
(autoload 'remember "remember" "\
;;;***
\f
-;;;### (autoloads (repeat) "repeat" "repeat.el" (20388 65061))
+;;;### (autoloads (repeat) "repeat" "repeat.el" (20412 11425))
;;; Generated autoloads from repeat.el
(autoload 'repeat "repeat" "\
;;;***
\f
;;;### (autoloads (reporter-submit-bug-report) "reporter" "mail/reporter.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from mail/reporter.el
(autoload 'reporter-submit-bug-report "reporter" "\
;;;***
\f
;;;### (autoloads (reposition-window) "reposition" "reposition.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from reposition.el
(autoload 'reposition-window "reposition" "\
;;;***
\f
;;;### (autoloads (global-reveal-mode reveal-mode) "reveal" "reveal.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from reveal.el
(autoload 'reveal-mode "reveal" "\
;;;***
\f
;;;### (autoloads (make-ring ring-p) "ring" "emacs-lisp/ring.el"
-;;;;;; (20355 10021))
+;;;;;; (20331 12564))
;;; Generated autoloads from emacs-lisp/ring.el
(autoload 'ring-p "ring" "\
;;;***
\f
-;;;### (autoloads (rlogin) "rlogin" "net/rlogin.el" (20402 11562))
+;;;### (autoloads (rlogin) "rlogin" "net/rlogin.el" (20412 11425))
;;; Generated autoloads from net/rlogin.el
(autoload 'rlogin "rlogin" "\
;;;;;; rmail-secondary-file-directory rmail-primary-inbox-list rmail-highlighted-headers
;;;;;; rmail-retry-ignored-headers rmail-displayed-headers rmail-ignored-headers
;;;;;; rmail-user-mail-address-regexp rmail-movemail-variant-p rmail-spool-directory
-;;;;;; rmail-file-name) "rmail" "mail/rmail.el" (20414 2727))
+;;;;;; rmail-file-name) "rmail" "mail/rmail.el" (20438 17064))
;;; Generated autoloads from mail/rmail.el
(defvar rmail-file-name (purecopy "~/RMAIL") "\
;;;***
\f
;;;### (autoloads (rmail-output-body-to-file rmail-output-as-seen
-;;;;;; rmail-output) "rmailout" "mail/rmailout.el" (20355 10021))
+;;;;;; rmail-output) "rmailout" "mail/rmailout.el" (20244 35516))
;;; Generated autoloads from mail/rmailout.el
(put 'rmail-output-file-alist 'risky-local-variable t)
;;;***
\f
;;;### (autoloads (rng-c-load-schema) "rng-cmpct" "nxml/rng-cmpct.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from nxml/rng-cmpct.el
(autoload 'rng-c-load-schema "rng-cmpct" "\
;;;***
\f
;;;### (autoloads (rng-nxml-mode-init) "rng-nxml" "nxml/rng-nxml.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from nxml/rng-nxml.el
(autoload 'rng-nxml-mode-init "rng-nxml" "\
;;;***
\f
;;;### (autoloads (rng-validate-mode) "rng-valid" "nxml/rng-valid.el"
-;;;;;; (20355 10021))
+;;;;;; (20290 33419))
;;; Generated autoloads from nxml/rng-valid.el
(autoload 'rng-validate-mode "rng-valid" "\
;;;***
\f
-;;;### (autoloads (rng-xsd-compile) "rng-xsd" "nxml/rng-xsd.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (rng-xsd-compile) "rng-xsd" "nxml/rng-xsd.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from nxml/rng-xsd.el
(put 'http://www\.w3\.org/2001/XMLSchema-datatypes 'rng-dt-compile 'rng-xsd-compile)
;;;***
\f
;;;### (autoloads (robin-use-package robin-modify-package robin-define-package)
-;;;;;; "robin" "international/robin.el" (20355 10021))
+;;;;;; "robin" "international/robin.el" (20428 57510))
;;; Generated autoloads from international/robin.el
(autoload 'robin-define-package "robin" "\
If there already exists a robin package whose name is NAME, the new
one replaces the old one.
-\(fn NAME DOCSTRING &rest RULES)" nil (quote macro))
+\(fn NAME DOCSTRING &rest RULES)" nil t)
(autoload 'robin-modify-package "robin" "\
Change a rule in an already defined robin package.
;;;***
\f
;;;### (autoloads (toggle-rot13-mode rot13-other-window rot13-region
-;;;;;; rot13-string rot13) "rot13" "rot13.el" (20355 10021))
+;;;;;; rot13-string rot13) "rot13" "rot13.el" (20244 35516))
;;; Generated autoloads from rot13.el
(autoload 'rot13 "rot13" "\
;;;***
\f
;;;### (autoloads (rst-minor-mode rst-mode) "rst" "textmodes/rst.el"
-;;;;;; (20421 62373))
+;;;;;; (20451 21022))
;;; Generated autoloads from textmodes/rst.el
(add-to-list 'auto-mode-alist (purecopy '("\\.re?st\\'" . rst-mode)))
;;;***
\f
;;;### (autoloads (ruby-mode) "ruby-mode" "progmodes/ruby-mode.el"
-;;;;;; (20375 53029))
+;;;;;; (20374 56770))
;;; Generated autoloads from progmodes/ruby-mode.el
(autoload 'ruby-mode "ruby-mode" "\
;;;***
\f
-;;;### (autoloads (ruler-mode) "ruler-mode" "ruler-mode.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (ruler-mode) "ruler-mode" "ruler-mode.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from ruler-mode.el
(defvar ruler-mode nil "\
;;;***
\f
-;;;### (autoloads (rx rx-to-string) "rx" "emacs-lisp/rx.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (rx rx-to-string) "rx" "emacs-lisp/rx.el" (20451
+;;;;;; 21074))
;;; Generated autoloads from emacs-lisp/rx.el
(autoload 'rx-to-string "rx" "\
`(regexp REGEXP)'
include REGEXP in string notation in the result.
-\(fn &rest REGEXPS)" nil (quote macro))
+\(fn &rest REGEXPS)" nil t)
;;;***
\f
-;;;### (autoloads (savehist-mode) "savehist" "savehist.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (savehist-mode) "savehist" "savehist.el" (20318
+;;;;;; 5885))
;;; Generated autoloads from savehist.el
(defvar savehist-mode nil "\
;;;***
\f
;;;### (autoloads (dsssl-mode scheme-mode) "scheme" "progmodes/scheme.el"
-;;;;;; (20355 10021))
+;;;;;; (20428 57510))
;;; Generated autoloads from progmodes/scheme.el
(autoload 'scheme-mode "scheme" "\
In addition, if an inferior Scheme process is running, some additional
commands will be defined, for evaluating expressions and controlling
the interpreter, and the state of the process will be displayed in the
-modeline of all Scheme buffers. The names of commands that interact
+mode line of all Scheme buffers. The names of commands that interact
with the Scheme process start with \"xscheme-\" if you use the MIT
Scheme-specific `xscheme' package; for more information see the
documentation for `xscheme-interaction-mode'. Use \\[run-scheme] to
;;;***
\f
;;;### (autoloads (gnus-score-mode) "score-mode" "gnus/score-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/score-mode.el
(autoload 'gnus-score-mode "score-mode" "\
;;;***
\f
;;;### (autoloads (scroll-all-mode) "scroll-all" "scroll-all.el"
-;;;;;; (20363 61861))
+;;;;;; (20373 41604))
;;; Generated autoloads from scroll-all.el
(defvar scroll-all-mode nil "\
;;;***
\f
;;;### (autoloads (scroll-lock-mode) "scroll-lock" "scroll-lock.el"
-;;;;;; (20355 10021))
+;;;;;; (20276 3849))
;;; Generated autoloads from scroll-lock.el
(autoload 'scroll-lock-mode "scroll-lock" "\
;;;***
\f
-;;;### (autoloads nil "secrets" "net/secrets.el" (20355 10021))
+;;;### (autoloads nil "secrets" "net/secrets.el" (20318 5885))
;;; Generated autoloads from net/secrets.el
(when (featurep 'dbusbind)
(autoload 'secrets-show-secrets "secrets" nil t))
;;;***
\f
;;;### (autoloads (semantic-mode semantic-default-submodes) "semantic"
-;;;;;; "cedet/semantic.el" (20355 10021))
+;;;;;; "cedet/semantic.el" (20356 35090))
;;; Generated autoloads from cedet/semantic.el
(defvar semantic-default-submodes '(global-semantic-idle-scheduler-mode global-semanticdb-minor-mode) "\
;;;;;; mail-personal-alias-file mail-default-reply-to mail-archive-file-name
;;;;;; mail-header-separator send-mail-function mail-interactive
;;;;;; mail-self-blind mail-specify-envelope-from mail-from-style)
-;;;;;; "sendmail" "mail/sendmail.el" (20417 65331))
+;;;;;; "sendmail" "mail/sendmail.el" (20419 46656))
;;; Generated autoloads from mail/sendmail.el
(defvar mail-from-style 'default "\
;;;***
\f
;;;### (autoloads (server-save-buffers-kill-terminal server-mode
-;;;;;; server-force-delete server-start) "server" "server.el" (20370
-;;;;;; 35109))
+;;;;;; server-force-delete server-start) "server" "server.el" (20373
+;;;;;; 41604))
;;; Generated autoloads from server.el
(put 'server-host 'risky-local-variable t)
;;;***
\f
-;;;### (autoloads (ses-mode) "ses" "ses.el" (20373 11301))
+;;;### (autoloads (ses-mode) "ses" "ses.el" (20428 57510))
;;; Generated autoloads from ses.el
(autoload 'ses-mode "ses" "\
;;;***
\f
;;;### (autoloads (html-mode sgml-mode) "sgml-mode" "textmodes/sgml-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20428 57510))
;;; Generated autoloads from textmodes/sgml-mode.el
(autoload 'sgml-mode "sgml-mode" "\
;;;***
\f
;;;### (autoloads (sh-mode) "sh-script" "progmodes/sh-script.el"
-;;;;;; (20397 18394))
+;;;;;; (20412 11425))
;;; Generated autoloads from progmodes/sh-script.el
(put 'sh-shell 'safe-local-variable 'symbolp)
;;;***
\f
;;;### (autoloads (list-load-path-shadows) "shadow" "emacs-lisp/shadow.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from emacs-lisp/shadow.el
(autoload 'list-load-path-shadows "shadow" "\
;;;***
\f
;;;### (autoloads (shadow-initialize shadow-define-regexp-group shadow-define-literal-group
-;;;;;; shadow-define-cluster) "shadowfile" "shadowfile.el" (20355
-;;;;;; 10021))
+;;;;;; shadow-define-cluster) "shadowfile" "shadowfile.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from shadowfile.el
(autoload 'shadow-define-cluster "shadowfile" "\
;;;***
\f
;;;### (autoloads (shell shell-dumb-shell-regexp) "shell" "shell.el"
-;;;;;; (20402 36105))
+;;;;;; (20412 11425))
;;; Generated autoloads from shell.el
(defvar shell-dumb-shell-regexp (purecopy "cmd\\(proxy\\)?\\.exe") "\
;;;***
\f
-;;;### (autoloads (shr-insert-document) "shr" "gnus/shr.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (shr-insert-document) "shr" "gnus/shr.el" (20446
+;;;;;; 34252))
;;; Generated autoloads from gnus/shr.el
(autoload 'shr-insert-document "shr" "\
;;;***
\f
;;;### (autoloads (sieve-upload-and-bury sieve-upload sieve-manage)
-;;;;;; "sieve" "gnus/sieve.el" (20355 10021))
+;;;;;; "sieve" "gnus/sieve.el" (20244 35516))
;;; Generated autoloads from gnus/sieve.el
(autoload 'sieve-manage "sieve" "\
;;;***
\f
;;;### (autoloads (sieve-mode) "sieve-mode" "gnus/sieve-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/sieve-mode.el
(autoload 'sieve-mode "sieve-mode" "\
;;;***
\f
-;;;### (autoloads (simula-mode) "simula" "progmodes/simula.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (simula-mode) "simula" "progmodes/simula.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from progmodes/simula.el
(autoload 'simula-mode "simula" "\
;;;***
\f
;;;### (autoloads (skeleton-pair-insert-maybe skeleton-insert skeleton-proxy-new
-;;;;;; define-skeleton) "skeleton" "skeleton.el" (20406 8611))
+;;;;;; define-skeleton) "skeleton" "skeleton.el" (20412 11425))
;;; Generated autoloads from skeleton.el
(defvar skeleton-filter-function 'identity "\
DOCUMENTATION is that of the command.
SKELETON is as defined under `skeleton-insert'.
-\(fn COMMAND DOCUMENTATION &rest SKELETON)" nil (quote macro))
+\(fn COMMAND DOCUMENTATION &rest SKELETON)" nil t)
(put 'define-skeleton 'doc-string-elt '2)
;;;***
\f
;;;### (autoloads (smerge-start-session smerge-mode smerge-ediff)
-;;;;;; "smerge-mode" "vc/smerge-mode.el" (20415 23587))
+;;;;;; "smerge-mode" "vc/smerge-mode.el" (20415 57974))
;;; Generated autoloads from vc/smerge-mode.el
(autoload 'smerge-ediff "smerge-mode" "\
;;;***
\f
;;;### (autoloads (smiley-buffer smiley-region) "smiley" "gnus/smiley.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/smiley.el
(autoload 'smiley-region "smiley" "\
;;;***
\f
;;;### (autoloads (smtpmail-send-queued-mail smtpmail-send-it) "smtpmail"
-;;;;;; "mail/smtpmail.el" (20402 11562))
+;;;;;; "mail/smtpmail.el" (20412 11425))
;;; Generated autoloads from mail/smtpmail.el
(autoload 'smtpmail-send-it "smtpmail" "\
;;;***
\f
-;;;### (autoloads (snake) "snake" "play/snake.el" (20355 10021))
+;;;### (autoloads (snake) "snake" "play/snake.el" (20244 35516))
;;; Generated autoloads from play/snake.el
(autoload 'snake "snake" "\
;;;***
\f
;;;### (autoloads (snmpv2-mode snmp-mode) "snmp-mode" "net/snmp-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from net/snmp-mode.el
(autoload 'snmp-mode "snmp-mode" "\
;;;***
\f
-;;;### (autoloads (sunrise-sunset) "solar" "calendar/solar.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (sunrise-sunset) "solar" "calendar/solar.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from calendar/solar.el
(autoload 'sunrise-sunset "solar" "\
;;;***
\f
-;;;### (autoloads (solitaire) "solitaire" "play/solitaire.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (solitaire) "solitaire" "play/solitaire.el" (20428
+;;;;;; 57510))
;;; Generated autoloads from play/solitaire.el
(autoload 'solitaire "solitaire" "\
\f
;;;### (autoloads (reverse-region sort-columns sort-regexp-fields
;;;;;; sort-fields sort-numeric-fields sort-pages sort-paragraphs
-;;;;;; sort-lines sort-subr) "sort" "sort.el" (20355 10021))
+;;;;;; sort-lines sort-subr) "sort" "sort.el" (20331 12564))
;;; Generated autoloads from sort.el
(put 'sort-fold-case 'safe-local-variable 'booleanp)
;;;***
\f
-;;;### (autoloads (spam-initialize) "spam" "gnus/spam.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (spam-initialize) "spam" "gnus/spam.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from gnus/spam.el
(autoload 'spam-initialize "spam" "\
\f
;;;### (autoloads (spam-report-deagentize spam-report-agentize spam-report-url-to-file
;;;;;; spam-report-url-ping-mm-url spam-report-process-queue) "spam-report"
-;;;;;; "gnus/spam-report.el" (20355 10021))
+;;;;;; "gnus/spam-report.el" (20244 35516))
;;; Generated autoloads from gnus/spam-report.el
(autoload 'spam-report-process-queue "spam-report" "\
;;;***
\f
;;;### (autoloads (speedbar-get-focus speedbar-frame-mode) "speedbar"
-;;;;;; "speedbar.el" (20399 35365))
+;;;;;; "speedbar.el" (20434 28080))
;;; Generated autoloads from speedbar.el
(defalias 'speedbar 'speedbar-frame-mode)
;;;***
\f
-;;;### (autoloads (snarf-spooks spook) "spook" "play/spook.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (snarf-spooks spook) "spook" "play/spook.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from play/spook.el
(autoload 'spook "spook" "\
;;;;;; sql-ms sql-ingres sql-solid sql-mysql sql-sqlite sql-informix
;;;;;; sql-sybase sql-oracle sql-product-interactive sql-connect
;;;;;; sql-mode sql-help sql-add-product-keywords) "sql" "progmodes/sql.el"
-;;;;;; (20355 10021))
+;;;;;; (20318 5885))
;;; Generated autoloads from progmodes/sql.el
(autoload 'sql-add-product-keywords "sql" "\
;;;***
\f
;;;### (autoloads (srecode-template-mode) "srecode/srt-mode" "cedet/srecode/srt-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from cedet/srecode/srt-mode.el
(autoload 'srecode-template-mode "srecode/srt-mode" "\
;;;***
\f
;;;### (autoloads (starttls-open-stream) "starttls" "gnus/starttls.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from gnus/starttls.el
(autoload 'starttls-open-stream "starttls" "\
;;;;;; strokes-mode strokes-list-strokes strokes-load-user-strokes
;;;;;; strokes-help strokes-describe-stroke strokes-do-complex-stroke
;;;;;; strokes-do-stroke strokes-read-complex-stroke strokes-read-stroke
-;;;;;; strokes-global-set-stroke) "strokes" "strokes.el" (20355
-;;;;;; 10021))
+;;;;;; strokes-global-set-stroke) "strokes" "strokes.el" (20428
+;;;;;; 57510))
;;; Generated autoloads from strokes.el
(autoload 'strokes-global-set-stroke "strokes" "\
;;;***
\f
;;;### (autoloads (studlify-buffer studlify-word studlify-region)
-;;;;;; "studly" "play/studly.el" (20355 10021))
+;;;;;; "studly" "play/studly.el" (19765 60663))
;;; Generated autoloads from play/studly.el
(autoload 'studlify-region "studly" "\
;;;***
\f
;;;### (autoloads (global-subword-mode subword-mode) "subword" "progmodes/subword.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from progmodes/subword.el
(autoload 'subword-mode "subword" "\
;;;***
\f
;;;### (autoloads (sc-cite-original) "supercite" "mail/supercite.el"
-;;;;;; (20355 10021))
+;;;;;; (20276 3849))
;;; Generated autoloads from mail/supercite.el
(autoload 'sc-cite-original "supercite" "\
;;;***
\f
-;;;### (autoloads (gpm-mouse-mode) "t-mouse" "t-mouse.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (gpm-mouse-mode) "t-mouse" "t-mouse.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from t-mouse.el
(define-obsolete-function-alias 't-mouse-mode 'gpm-mouse-mode "23.1")
;;;***
\f
-;;;### (autoloads (tabify untabify) "tabify" "tabify.el" (20355 10021))
+;;;### (autoloads (tabify untabify) "tabify" "tabify.el" (20244 35516))
;;; Generated autoloads from tabify.el
(autoload 'untabify "tabify" "\
;;;;;; table-recognize table-insert-row-column table-insert-column
;;;;;; table-insert-row table-insert table-point-left-cell-hook
;;;;;; table-point-entered-cell-hook table-load-hook table-cell-map-hook)
-;;;;;; "table" "textmodes/table.el" (20355 10021))
+;;;;;; "table" "textmodes/table.el" (20434 28080))
;;; Generated autoloads from textmodes/table.el
(defvar table-cell-map-hook nil "\
;;;***
\f
-;;;### (autoloads (talk talk-connect) "talk" "talk.el" (20355 10021))
+;;;### (autoloads (talk talk-connect) "talk" "talk.el" (20244 35516))
;;; Generated autoloads from talk.el
(autoload 'talk-connect "talk" "\
;;;***
\f
-;;;### (autoloads (tar-mode) "tar-mode" "tar-mode.el" (20387 44199))
+;;;### (autoloads (tar-mode) "tar-mode" "tar-mode.el" (20412 11425))
;;; Generated autoloads from tar-mode.el
(autoload 'tar-mode "tar-mode" "\
;;;***
\f
;;;### (autoloads (tcl-help-on-word inferior-tcl tcl-mode) "tcl"
-;;;;;; "progmodes/tcl.el" (20355 10021))
+;;;;;; "progmodes/tcl.el" (20356 35090))
;;; Generated autoloads from progmodes/tcl.el
(autoload 'tcl-mode "tcl" "\
;;;***
\f
-;;;### (autoloads (rsh telnet) "telnet" "net/telnet.el" (20355 10021))
+;;;### (autoloads (rsh telnet) "telnet" "net/telnet.el" (20244 35516))
;;; Generated autoloads from net/telnet.el
(autoload 'telnet "telnet" "\
;;;***
\f
;;;### (autoloads (serial-term ansi-term term make-term) "term" "term.el"
-;;;;;; (20397 18394))
+;;;;;; (20451 20881))
;;; Generated autoloads from term.el
(autoload 'make-term "term" "\
;;;***
\f
-;;;### (autoloads (terminal-emulator) "terminal" "terminal.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (terminal-emulator) "terminal" "terminal.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from terminal.el
(autoload 'terminal-emulator "terminal" "\
;;;***
\f
;;;### (autoloads (testcover-this-defun) "testcover" "emacs-lisp/testcover.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from emacs-lisp/testcover.el
(autoload 'testcover-this-defun "testcover" "\
;;;***
\f
-;;;### (autoloads (tetris) "tetris" "play/tetris.el" (20355 10021))
+;;;### (autoloads (tetris) "tetris" "play/tetris.el" (20244 35516))
;;; Generated autoloads from play/tetris.el
(autoload 'tetris "tetris" "\
;;;;;; tex-start-commands tex-start-options slitex-run-command latex-run-command
;;;;;; tex-run-command tex-offer-save tex-main-file tex-first-line-header-regexp
;;;;;; tex-directory tex-shell-file-name) "tex-mode" "textmodes/tex-mode.el"
-;;;;;; (20364 45187))
+;;;;;; (20446 34252))
;;; Generated autoloads from textmodes/tex-mode.el
(defvar tex-shell-file-name nil "\
;;;***
\f
;;;### (autoloads (texi2info texinfo-format-region texinfo-format-buffer)
-;;;;;; "texinfmt" "textmodes/texinfmt.el" (20355 10021))
+;;;;;; "texinfmt" "textmodes/texinfmt.el" (20434 28080))
;;; Generated autoloads from textmodes/texinfmt.el
(autoload 'texinfo-format-buffer "texinfmt" "\
;;;***
\f
;;;### (autoloads (texinfo-mode texinfo-close-quote texinfo-open-quote)
-;;;;;; "texinfo" "textmodes/texinfo.el" (20355 10021))
+;;;;;; "texinfo" "textmodes/texinfo.el" (20244 35516))
;;; Generated autoloads from textmodes/texinfo.el
(defvar texinfo-open-quote (purecopy "``") "\
\f
;;;### (autoloads (thai-composition-function thai-compose-buffer
;;;;;; thai-compose-string thai-compose-region) "thai-util" "language/thai-util.el"
-;;;;;; (20355 10021))
+;;;;;; (20276 3849))
;;; Generated autoloads from language/thai-util.el
(autoload 'thai-compose-region "thai-util" "\
\f
;;;### (autoloads (list-at-point number-at-point symbol-at-point
;;;;;; sexp-at-point thing-at-point bounds-of-thing-at-point forward-thing)
-;;;;;; "thingatpt" "thingatpt.el" (20416 44451))
+;;;;;; "thingatpt" "thingatpt.el" (20419 46656))
;;; Generated autoloads from thingatpt.el
(autoload 'forward-thing "thingatpt" "\
\f
;;;### (autoloads (thumbs-dired-setroot thumbs-dired-show thumbs-dired-show-marked
;;;;;; thumbs-show-from-dir thumbs-find-thumb) "thumbs" "thumbs.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from thumbs.el
(autoload 'thumbs-find-thumb "thumbs" "\
;;;;;; tibetan-post-read-conversion tibetan-compose-buffer tibetan-decompose-buffer
;;;;;; tibetan-decompose-string tibetan-decompose-region tibetan-compose-region
;;;;;; tibetan-compose-string tibetan-transcription-to-tibetan tibetan-tibetan-to-transcription
-;;;;;; tibetan-char-p) "tibet-util" "language/tibet-util.el" (20355
-;;;;;; 10021))
+;;;;;; tibetan-char-p) "tibet-util" "language/tibet-util.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from language/tibet-util.el
(autoload 'tibetan-char-p "tibet-util" "\
;;;***
\f
;;;### (autoloads (tildify-buffer tildify-region) "tildify" "textmodes/tildify.el"
-;;;;;; (20373 11301))
+;;;;;; (20373 41604))
;;; Generated autoloads from textmodes/tildify.el
(autoload 'tildify-region "tildify" "\
\f
;;;### (autoloads (emacs-init-time emacs-uptime display-time-world
;;;;;; display-time-mode display-time display-time-day-and-date)
-;;;;;; "time" "time.el" (20387 44199))
+;;;;;; "time" "time.el" (20412 11425))
;;; Generated autoloads from time.el
(defvar display-time-day-and-date nil "\
;;;;;; time-to-day-in-year date-leap-year-p days-between date-to-day
;;;;;; time-add time-subtract time-since days-to-time time-less-p
;;;;;; seconds-to-time date-to-time) "time-date" "calendar/time-date.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from calendar/time-date.el
(autoload 'date-to-time "time-date" "\
;;;***
\f
;;;### (autoloads (time-stamp-toggle-active time-stamp) "time-stamp"
-;;;;;; "time-stamp.el" (20355 10021))
+;;;;;; "time-stamp.el" (20244 35516))
;;; Generated autoloads from time-stamp.el
(put 'time-stamp-format 'safe-local-variable 'stringp)
(put 'time-stamp-time-zone 'safe-local-variable 'string-or-null-p)
;;;### (autoloads (timeclock-when-to-leave-string timeclock-workday-elapsed-string
;;;;;; timeclock-workday-remaining-string timeclock-reread-log timeclock-query-out
;;;;;; timeclock-change timeclock-status-string timeclock-out timeclock-in
-;;;;;; timeclock-modeline-display) "timeclock" "calendar/timeclock.el"
-;;;;;; (20355 10021))
+;;;;;; timeclock-mode-line-display) "timeclock" "calendar/timeclock.el"
+;;;;;; (20428 57510))
;;; Generated autoloads from calendar/timeclock.el
-(autoload 'timeclock-modeline-display "timeclock" "\
-Toggle display of the amount of time left today in the modeline.
+(autoload 'timeclock-mode-line-display "timeclock" "\
+Toggle display of the amount of time left today in the mode line.
If `timeclock-use-display-time' is non-nil (the default), then
-the function `display-time-mode' must be active, and the modeline
+the function `display-time-mode' must be active, and the mode line
will be updated whenever the time display is updated. Otherwise,
the timeclock will use its own sixty second timer to do its
-updating. With prefix ARG, turn modeline display on if and only
-if ARG is positive. Returns the new status of timeclock modeline
+updating. With prefix ARG, turn mode line display on if and only
+if ARG is positive. Returns the new status of timeclock mode line
display (non-nil means on).
\(fn &optional ARG)" t nil)
;;;***
\f
;;;### (autoloads (batch-titdic-convert titdic-convert) "titdic-cnv"
-;;;;;; "international/titdic-cnv.el" (20355 10021))
+;;;;;; "international/titdic-cnv.el" (20290 33419))
;;; Generated autoloads from international/titdic-cnv.el
(autoload 'titdic-convert "titdic-cnv" "\
;;;***
\f
;;;### (autoloads (tmm-prompt tmm-menubar-mouse tmm-menubar) "tmm"
-;;;;;; "tmm.el" (20356 55829))
+;;;;;; "tmm.el" (20432 55251))
;;; Generated autoloads from tmm.el
(define-key global-map "\M-`" 'tmm-menubar)
(define-key global-map [menu-bar mouse-1] 'tmm-menubar-mouse)
\f
;;;### (autoloads (todo-show todo-cp todo-mode todo-print todo-top-priorities
;;;;;; todo-insert-item todo-add-item-non-interactively todo-add-category)
-;;;;;; "todo-mode" "calendar/todo-mode.el" (20355 10021))
+;;;;;; "todo-mode" "calendar/todo-mode.el" (20244 35516))
;;; Generated autoloads from calendar/todo-mode.el
(autoload 'todo-add-category "todo-mode" "\
\f
;;;### (autoloads (tool-bar-local-item-from-menu tool-bar-add-item-from-menu
;;;;;; tool-bar-local-item tool-bar-add-item toggle-tool-bar-mode-from-frame)
-;;;;;; "tool-bar" "tool-bar.el" (20355 10021))
+;;;;;; "tool-bar" "tool-bar.el" (20290 33419))
;;; Generated autoloads from tool-bar.el
(autoload 'toggle-tool-bar-mode-from-frame "tool-bar" "\
;;;***
\f
;;;### (autoloads (tpu-edt-on tpu-edt-mode) "tpu-edt" "emulation/tpu-edt.el"
-;;;;;; (20399 35365))
+;;;;;; (20412 11425))
;;; Generated autoloads from emulation/tpu-edt.el
(defvar tpu-edt-mode nil "\
;;;***
\f
;;;### (autoloads (tpu-mapper) "tpu-mapper" "emulation/tpu-mapper.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from emulation/tpu-mapper.el
(autoload 'tpu-mapper "tpu-mapper" "\
;;;***
\f
-;;;### (autoloads (tq-create) "tq" "emacs-lisp/tq.el" (20355 10021))
+;;;### (autoloads (tq-create) "tq" "emacs-lisp/tq.el" (20244 35516))
;;; Generated autoloads from emacs-lisp/tq.el
(autoload 'tq-create "tq" "\
;;;***
\f
;;;### (autoloads (trace-function-background trace-function trace-buffer)
-;;;;;; "trace" "emacs-lisp/trace.el" (20355 10021))
+;;;;;; "trace" "emacs-lisp/trace.el" (20244 35516))
;;; Generated autoloads from emacs-lisp/trace.el
(defvar trace-buffer (purecopy "*trace-output*") "\
;;;### (autoloads (tramp-unload-tramp tramp-completion-handle-file-name-completion
;;;;;; tramp-completion-handle-file-name-all-completions tramp-unload-file-name-handlers
;;;;;; tramp-file-name-handler tramp-syntax tramp-mode) "tramp"
-;;;;;; "net/tramp.el" (20373 11301))
+;;;;;; "net/tramp.el" (20446 34252))
;;; Generated autoloads from net/tramp.el
(defvar tramp-mode t "\
(custom-autoload 'tramp-syntax "tramp" t)
-(defconst tramp-file-name-regexp-unified (if (memq system-type '(cygwin windows-nt)) "\\`/\\([^[/:]\\{2,\\}\\|[^/]\\{2,\\}]\\):" "\\`/\\([^[/:]+\\|[^/]+]\\):") "\
+(defconst tramp-file-name-regexp-unified (if (memq system-type '(cygwin windows-nt)) "\\`/\\([^[/|:]\\{2,\\}\\|[^/|]\\{2,\\}]\\):" "\\`/\\([^[/|:]+\\|[^/|]+]\\):") "\
Value for `tramp-file-name-regexp' for unified remoting.
Emacs (not XEmacs) uses a unified filename syntax for Ange-FTP and
Tramp. See `tramp-file-name-structure' for more explanations.
XEmacs uses a separate filename syntax for Tramp and EFS.
See `tramp-file-name-structure' for more explanations.")
-(defconst tramp-file-name-regexp-url "\\`/[^/:]+://" "\
+(defconst tramp-file-name-regexp-url "\\`/[^/|:]+://" "\
Value for `tramp-file-name-regexp' for URL-like remoting.
See `tramp-file-name-structure' for more explanations.")
;;;***
\f
;;;### (autoloads (tramp-ftp-enable-ange-ftp) "tramp-ftp" "net/tramp-ftp.el"
-;;;;;; (20355 10021))
+;;;;;; (20438 17064))
;;; Generated autoloads from net/tramp-ftp.el
(autoload 'tramp-ftp-enable-ange-ftp "tramp-ftp" "\
;;;***
\f
-;;;### (autoloads (help-with-tutorial) "tutorial" "tutorial.el" (20369
-;;;;;; 14251))
+;;;### (autoloads (help-with-tutorial) "tutorial" "tutorial.el" (20373
+;;;;;; 41604))
;;; Generated autoloads from tutorial.el
(autoload 'help-with-tutorial "tutorial" "\
;;;***
\f
;;;### (autoloads (tai-viet-composition-function) "tv-util" "language/tv-util.el"
-;;;;;; (20355 10021))
+;;;;;; (19765 60663))
;;; Generated autoloads from language/tv-util.el
(autoload 'tai-viet-composition-function "tv-util" "\
;;;***
\f
;;;### (autoloads (2C-split 2C-associate-buffer 2C-two-columns) "two-column"
-;;;;;; "textmodes/two-column.el" (20364 31990))
+;;;;;; "textmodes/two-column.el" (20373 41604))
;;; Generated autoloads from textmodes/two-column.el
(autoload '2C-command "two-column" () t 'keymap)
(global-set-key "\C-x6" '2C-command)
;;;;;; type-break type-break-mode type-break-keystroke-threshold
;;;;;; type-break-good-break-interval type-break-good-rest-interval
;;;;;; type-break-interval type-break-mode) "type-break" "type-break.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from type-break.el
(defvar type-break-mode nil "\
;;;***
\f
-;;;### (autoloads (uce-reply-to-uce) "uce" "mail/uce.el" (20355 10021))
+;;;### (autoloads (uce-reply-to-uce) "uce" "mail/uce.el" (20244 35516))
;;; Generated autoloads from mail/uce.el
(autoload 'uce-reply-to-uce "uce" "\
;;;;;; ucs-normalize-NFKC-string ucs-normalize-NFKC-region ucs-normalize-NFKD-string
;;;;;; ucs-normalize-NFKD-region ucs-normalize-NFC-string ucs-normalize-NFC-region
;;;;;; ucs-normalize-NFD-string ucs-normalize-NFD-region) "ucs-normalize"
-;;;;;; "international/ucs-normalize.el" (20355 10021))
+;;;;;; "international/ucs-normalize.el" (20244 35516))
;;; Generated autoloads from international/ucs-normalize.el
(autoload 'ucs-normalize-NFD-region "ucs-normalize" "\
;;;***
\f
;;;### (autoloads (ununderline-region underline-region) "underline"
-;;;;;; "textmodes/underline.el" (20355 10021))
+;;;;;; "textmodes/underline.el" (20244 35516))
;;; Generated autoloads from textmodes/underline.el
(autoload 'underline-region "underline" "\
;;;***
\f
;;;### (autoloads (unrmail batch-unrmail) "unrmail" "mail/unrmail.el"
-;;;;;; (20369 14251))
+;;;;;; (20373 41604))
;;; Generated autoloads from mail/unrmail.el
(autoload 'batch-unrmail "unrmail" "\
;;;***
\f
-;;;### (autoloads (unsafep) "unsafep" "emacs-lisp/unsafep.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (unsafep) "unsafep" "emacs-lisp/unsafep.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from emacs-lisp/unsafep.el
(autoload 'unsafep "unsafep" "\
;;;***
\f
;;;### (autoloads (url-retrieve-synchronously url-retrieve) "url"
-;;;;;; "url/url.el" (20394 17446))
+;;;;;; "url/url.el" (20451 20881))
;;; Generated autoloads from url/url.el
(autoload 'url-retrieve "url" "\
;;;***
\f
;;;### (autoloads (url-register-auth-scheme url-get-authentication)
-;;;;;; "url-auth" "url/url-auth.el" (20355 10021))
+;;;;;; "url-auth" "url/url-auth.el" (20244 35516))
;;; Generated autoloads from url/url-auth.el
(autoload 'url-get-authentication "url-auth" "\
;;;***
\f
;;;### (autoloads (url-cache-extract url-is-cached url-store-in-cache)
-;;;;;; "url-cache" "url/url-cache.el" (20355 10021))
+;;;;;; "url-cache" "url/url-cache.el" (20276 3849))
;;; Generated autoloads from url/url-cache.el
(autoload 'url-store-in-cache "url-cache" "\
;;;***
\f
-;;;### (autoloads (url-cid) "url-cid" "url/url-cid.el" (20355 10021))
+;;;### (autoloads (url-cid) "url-cid" "url/url-cid.el" (20244 35516))
;;; Generated autoloads from url/url-cid.el
(autoload 'url-cid "url-cid" "\
;;;***
\f
;;;### (autoloads (url-dav-vc-registered url-dav-supported-p) "url-dav"
-;;;;;; "url/url-dav.el" (20355 10021))
+;;;;;; "url/url-dav.el" (20356 35090))
;;; Generated autoloads from url/url-dav.el
(autoload 'url-dav-supported-p "url-dav" "\
;;;***
\f
-;;;### (autoloads (url-file) "url-file" "url/url-file.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (url-file) "url-file" "url/url-file.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from url/url-file.el
(autoload 'url-file "url-file" "\
;;;***
\f
;;;### (autoloads (url-open-stream url-gateway-nslookup-host) "url-gw"
-;;;;;; "url/url-gw.el" (20355 10021))
+;;;;;; "url/url-gw.el" (20244 35516))
;;; Generated autoloads from url/url-gw.el
(autoload 'url-gateway-nslookup-host "url-gw" "\
\f
;;;### (autoloads (url-insert-file-contents url-file-local-copy url-copy-file
;;;;;; url-file-handler url-handler-mode) "url-handlers" "url/url-handlers.el"
-;;;;;; (20355 10021))
+;;;;;; (20446 34252))
;;; Generated autoloads from url/url-handlers.el
(defvar url-handler-mode nil "\
;;;***
\f
;;;### (autoloads (url-http-options url-http-file-attributes url-http-file-exists-p
-;;;;;; url-http) "url-http" "url/url-http.el" (20415 53309))
+;;;;;; url-http) "url-http" "url/url-http.el" (20415 57974))
;;; Generated autoloads from url/url-http.el
(autoload 'url-http "url-http" "\
;;;***
\f
-;;;### (autoloads (url-irc) "url-irc" "url/url-irc.el" (20355 10021))
+;;;### (autoloads (url-irc) "url-irc" "url/url-irc.el" (20244 35516))
;;; Generated autoloads from url/url-irc.el
(autoload 'url-irc "url-irc" "\
;;;***
\f
-;;;### (autoloads (url-ldap) "url-ldap" "url/url-ldap.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (url-ldap) "url-ldap" "url/url-ldap.el" (20356
+;;;;;; 35090))
;;; Generated autoloads from url/url-ldap.el
(autoload 'url-ldap "url-ldap" "\
;;;***
\f
;;;### (autoloads (url-mailto url-mail) "url-mailto" "url/url-mailto.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from url/url-mailto.el
(autoload 'url-mail "url-mailto" "\
;;;***
\f
;;;### (autoloads (url-data url-generic-emulator-loader url-info
-;;;;;; url-man) "url-misc" "url/url-misc.el" (20355 10021))
+;;;;;; url-man) "url-misc" "url/url-misc.el" (20244 35516))
;;; Generated autoloads from url/url-misc.el
(autoload 'url-man "url-misc" "\
;;;***
\f
;;;### (autoloads (url-snews url-news) "url-news" "url/url-news.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from url/url-news.el
(autoload 'url-news "url-news" "\
\f
;;;### (autoloads (url-ns-user-pref url-ns-prefs isInNet isResolvable
;;;;;; dnsResolve dnsDomainIs isPlainHostName) "url-ns" "url/url-ns.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from url/url-ns.el
(autoload 'isPlainHostName "url-ns" "\
;;;***
\f
;;;### (autoloads (url-generic-parse-url url-recreate-url) "url-parse"
-;;;;;; "url/url-parse.el" (20395 38306))
+;;;;;; "url/url-parse.el" (20412 11425))
;;; Generated autoloads from url/url-parse.el
(autoload 'url-recreate-url "url-parse" "\
;;;***
\f
;;;### (autoloads (url-setup-privacy-info) "url-privacy" "url/url-privacy.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from url/url-privacy.el
(autoload 'url-setup-privacy-info "url-privacy" "\
;;;***
\f
;;;### (autoloads (url-queue-retrieve) "url-queue" "url/url-queue.el"
-;;;;;; (20355 10021))
+;;;;;; (20336 29137))
;;; Generated autoloads from url/url-queue.el
(autoload 'url-queue-retrieve "url-queue" "\
;;;;;; url-percentage url-display-percentage url-pretty-length url-strip-leading-spaces
;;;;;; url-eat-trailing-space url-get-normalized-date url-lazy-message
;;;;;; url-normalize-url url-insert-entities-in-string url-parse-args
-;;;;;; url-debug url-debug) "url-util" "url/url-util.el" (20402
-;;;;;; 11562))
+;;;;;; url-debug url-debug) "url-util" "url/url-util.el" (20412
+;;;;;; 11425))
;;; Generated autoloads from url/url-util.el
(defvar url-debug nil "\
;;;***
\f
;;;### (autoloads (ask-user-about-supersession-threat ask-user-about-lock)
-;;;;;; "userlock" "userlock.el" (20355 10021))
+;;;;;; "userlock" "userlock.el" (20244 35516))
;;; Generated autoloads from userlock.el
(autoload 'ask-user-about-lock "userlock" "\
\f
;;;### (autoloads (utf-7-imap-pre-write-conversion utf-7-pre-write-conversion
;;;;;; utf-7-imap-post-read-conversion utf-7-post-read-conversion)
-;;;;;; "utf-7" "international/utf-7.el" (20355 10021))
+;;;;;; "utf-7" "international/utf-7.el" (20244 35516))
;;; Generated autoloads from international/utf-7.el
(autoload 'utf-7-post-read-conversion "utf-7" "\
;;;***
\f
-;;;### (autoloads (utf7-encode) "utf7" "gnus/utf7.el" (20355 10021))
+;;;### (autoloads (utf7-encode) "utf7" "gnus/utf7.el" (20244 35516))
;;; Generated autoloads from gnus/utf7.el
(autoload 'utf7-encode "utf7" "\
\f
;;;### (autoloads (uudecode-decode-region uudecode-decode-region-internal
;;;;;; uudecode-decode-region-external) "uudecode" "mail/uudecode.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from mail/uudecode.el
(autoload 'uudecode-decode-region-external "uudecode" "\
;;;;;; vc-print-log vc-retrieve-tag vc-create-tag vc-merge vc-insert-headers
;;;;;; vc-revision-other-window vc-root-diff vc-ediff vc-version-ediff
;;;;;; vc-diff vc-version-diff vc-register vc-next-action vc-before-checkin-hook
-;;;;;; vc-checkin-hook vc-checkout-hook) "vc" "vc/vc.el" (20421
-;;;;;; 62373))
+;;;;;; vc-checkin-hook vc-checkout-hook) "vc" "vc/vc.el" (20420
+;;;;;; 52684))
;;; Generated autoloads from vc/vc.el
(defvar vc-checkout-hook nil "\
;;;***
\f
;;;### (autoloads (vc-annotate) "vc-annotate" "vc/vc-annotate.el"
-;;;;;; (20356 55829))
+;;;;;; (20432 54738))
;;; Generated autoloads from vc/vc-annotate.el
(autoload 'vc-annotate "vc-annotate" "\
;;;***
\f
-;;;### (autoloads nil "vc-arch" "vc/vc-arch.el" (20377 8374))
+;;;### (autoloads nil "vc-arch" "vc/vc-arch.el" (20428 57510))
;;; Generated autoloads from vc/vc-arch.el
(defun vc-arch-registered (file)
(if (vc-find-root file "{arch}/=tagging-method")
;;;***
\f
-;;;### (autoloads nil "vc-bzr" "vc/vc-bzr.el" (20406 55122))
+;;;### (autoloads nil "vc-bzr" "vc/vc-bzr.el" (20412 11425))
;;; Generated autoloads from vc/vc-bzr.el
(defconst vc-bzr-admin-dirname ".bzr" "\
;;;***
\f
-;;;### (autoloads nil "vc-cvs" "vc/vc-cvs.el" (20377 8374))
+;;;### (autoloads nil "vc-cvs" "vc/vc-cvs.el" (20428 57510))
;;; Generated autoloads from vc/vc-cvs.el
(defun vc-cvs-registered (f)
"Return non-nil if file F is registered with CVS."
;;;***
\f
-;;;### (autoloads (vc-dir) "vc-dir" "vc/vc-dir.el" (20377 8374))
+;;;### (autoloads (vc-dir) "vc-dir" "vc/vc-dir.el" (20377 36640))
;;; Generated autoloads from vc/vc-dir.el
(autoload 'vc-dir "vc-dir" "\
;;;***
\f
;;;### (autoloads (vc-do-command) "vc-dispatcher" "vc/vc-dispatcher.el"
-;;;;;; (20364 45187))
+;;;;;; (20373 41604))
;;; Generated autoloads from vc/vc-dispatcher.el
(autoload 'vc-do-command "vc-dispatcher" "\
;;;***
\f
-;;;### (autoloads nil "vc-git" "vc/vc-git.el" (20378 29222))
+;;;### (autoloads nil "vc-git" "vc/vc-git.el" (20428 57510))
;;; Generated autoloads from vc/vc-git.el
(defun vc-git-registered (file)
"Return non-nil if FILE is registered with git."
;;;***
\f
-;;;### (autoloads nil "vc-hg" "vc/vc-hg.el" (20377 8374))
+;;;### (autoloads nil "vc-hg" "vc/vc-hg.el" (20377 36640))
;;; Generated autoloads from vc/vc-hg.el
(defun vc-hg-registered (file)
"Return non-nil if FILE is registered with hg."
;;;***
\f
-;;;### (autoloads nil "vc-mtn" "vc/vc-mtn.el" (20377 8374))
+;;;### (autoloads nil "vc-mtn" "vc/vc-mtn.el" (20428 57510))
;;; Generated autoloads from vc/vc-mtn.el
(defconst vc-mtn-admin-dir "_MTN" "\
;;;***
\f
;;;### (autoloads (vc-rcs-master-templates) "vc-rcs" "vc/vc-rcs.el"
-;;;;;; (20355 10021))
+;;;;;; (20432 42254))
;;; Generated autoloads from vc/vc-rcs.el
(defvar vc-rcs-master-templates (purecopy '("%sRCS/%s,v" "%s%s,v" "%sRCS/%s")) "\
;;;***
\f
;;;### (autoloads (vc-sccs-master-templates) "vc-sccs" "vc/vc-sccs.el"
-;;;;;; (20355 10021))
+;;;;;; (20432 42254))
;;; Generated autoloads from vc/vc-sccs.el
(defvar vc-sccs-master-templates (purecopy '("%sSCCS/s.%s" "%ss.%s" vc-sccs-search-project-dir)) "\
;;;***
\f
-;;;### (autoloads nil "vc-svn" "vc/vc-svn.el" (20355 10021))
+;;;### (autoloads nil "vc-svn" "vc/vc-svn.el" (20318 5885))
;;; Generated autoloads from vc/vc-svn.el
(defun vc-svn-registered (f)
(let ((admin-dir (cond ((and (eq system-type 'windows-nt)
;;;***
\f
;;;### (autoloads (vera-mode) "vera-mode" "progmodes/vera-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20434 28080))
;;; Generated autoloads from progmodes/vera-mode.el
(add-to-list 'auto-mode-alist (cons (purecopy "\\.vr[hi]?\\'") 'vera-mode))
;;;***
\f
;;;### (autoloads (verilog-mode) "verilog-mode" "progmodes/verilog-mode.el"
-;;;;;; (20420 41510))
+;;;;;; (20420 52684))
;;; Generated autoloads from progmodes/verilog-mode.el
(autoload 'verilog-mode "verilog-mode" "\
;;;***
\f
;;;### (autoloads (vhdl-mode) "vhdl-mode" "progmodes/vhdl-mode.el"
-;;;;;; (20419 20644))
+;;;;;; (20428 57510))
;;; Generated autoloads from progmodes/vhdl-mode.el
(autoload 'vhdl-mode "vhdl-mode" "\
brackets and removed if the queried string is left empty. Prompts for
mandatory arguments remain in the code if the queried string is left
empty. They can be queried again by `C-c C-t C-q'. Enabled
- electrification is indicated by `/e' in the modeline.
+ electrification is indicated by `/e' in the mode line.
Typing `M-SPC' after a keyword inserts a space without calling the
template generator. Automatic template generation (i.e.
Double striking of some keys inserts cumbersome VHDL syntax elements.
Stuttering can be disabled (enabled) by typing `C-c C-m C-s' or by
option `vhdl-stutter-mode'. Enabled stuttering is indicated by `/s' in
- the modeline. The stuttering keys and their effects are:
+ the mode line. The stuttering keys and their effects are:
;; --> \" : \" [ --> ( -- --> comment
;;; --> \" := \" [[ --> [ --CR --> comment-out code
;;;***
\f
-;;;### (autoloads (vi-mode) "vi" "emulation/vi.el" (20355 10021))
+;;;### (autoloads (vi-mode) "vi" "emulation/vi.el" (20107 60012))
;;; Generated autoloads from emulation/vi.el
(autoload 'vi-mode "vi" "\
;;;### (autoloads (viqr-pre-write-conversion viqr-post-read-conversion
;;;;;; viet-encode-viqr-buffer viet-encode-viqr-region viet-decode-viqr-buffer
;;;;;; viet-decode-viqr-region viet-encode-viscii-char) "viet-util"
-;;;;;; "language/viet-util.el" (20355 10021))
+;;;;;; "language/viet-util.el" (20244 35516))
;;; Generated autoloads from language/viet-util.el
(autoload 'viet-encode-viscii-char "viet-util" "\
;;;;;; view-mode view-buffer-other-frame view-buffer-other-window
;;;;;; view-buffer view-file-other-frame view-file-other-window
;;;;;; view-file kill-buffer-if-not-modified view-remove-frame-by-deleting)
-;;;;;; "view" "view.el" (20355 10021))
+;;;;;; "view" "view.el" (20331 12564))
;;; Generated autoloads from view.el
(defvar view-remove-frame-by-deleting t "\
;;;***
\f
-;;;### (autoloads (vip-mode vip-setup) "vip" "emulation/vip.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (vip-mode vip-setup) "vip" "emulation/vip.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from emulation/vip.el
(autoload 'vip-setup "vip" "\
;;;***
\f
;;;### (autoloads (viper-mode toggle-viper-mode) "viper" "emulation/viper.el"
-;;;;;; (20355 10021))
+;;;;;; (20356 35090))
;;; Generated autoloads from emulation/viper.el
(autoload 'toggle-viper-mode "viper" "\
;;;***
\f
;;;### (autoloads (warn lwarn display-warning) "warnings" "emacs-lisp/warnings.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from emacs-lisp/warnings.el
(defvar warning-prefix-function nil "\
;;;***
\f
;;;### (autoloads (wdired-change-to-wdired-mode) "wdired" "wdired.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from wdired.el
(autoload 'wdired-change-to-wdired-mode "wdired" "\
;;;***
\f
-;;;### (autoloads (webjump) "webjump" "net/webjump.el" (20355 10021))
+;;;### (autoloads (webjump) "webjump" "net/webjump.el" (20356 35090))
;;; Generated autoloads from net/webjump.el
(autoload 'webjump "webjump" "\
;;;***
\f
;;;### (autoloads (which-function-mode which-func-mode) "which-func"
-;;;;;; "progmodes/which-func.el" (20412 47398))
+;;;;;; "progmodes/which-func.el" (20428 57510))
;;; Generated autoloads from progmodes/which-func.el
(put 'which-func-format 'risky-local-variable t)
(put 'which-func-current 'risky-local-variable t)
;;;### (autoloads (whitespace-report-region whitespace-report whitespace-cleanup-region
;;;;;; whitespace-cleanup global-whitespace-toggle-options whitespace-toggle-options
;;;;;; global-whitespace-newline-mode global-whitespace-mode whitespace-newline-mode
-;;;;;; whitespace-mode) "whitespace" "whitespace.el" (20421 62373))
+;;;;;; whitespace-mode) "whitespace" "whitespace.el" (20434 28080))
;;; Generated autoloads from whitespace.el
(autoload 'whitespace-mode "whitespace" "\
;;;***
\f
;;;### (autoloads (widget-minor-mode widget-browse-other-window widget-browse
-;;;;;; widget-browse-at) "wid-browse" "wid-browse.el" (20355 10021))
+;;;;;; widget-browse-at) "wid-browse" "wid-browse.el" (20276 3849))
;;; Generated autoloads from wid-browse.el
(autoload 'widget-browse-at "wid-browse" "\
\f
;;;### (autoloads (widget-setup widget-insert widget-delete widget-create
;;;;;; widget-prompt-value widgetp) "wid-edit" "wid-edit.el" (20373
-;;;;;; 11301))
+;;;;;; 41604))
;;; Generated autoloads from wid-edit.el
(autoload 'widgetp "wid-edit" "\
;;;***
\f
;;;### (autoloads (windmove-default-keybindings windmove-down windmove-right
-;;;;;; windmove-up windmove-left) "windmove" "windmove.el" (20355
-;;;;;; 10021))
+;;;;;; windmove-up windmove-left) "windmove" "windmove.el" (20253
+;;;;;; 50954))
;;; Generated autoloads from windmove.el
(autoload 'windmove-left "windmove" "\
;;;***
\f
;;;### (autoloads (winner-mode winner-mode) "winner" "winner.el"
-;;;;;; (20355 10021))
+;;;;;; (20244 35516))
;;; Generated autoloads from winner.el
(defvar winner-mode nil "\
;;;***
\f
;;;### (autoloads (woman-bookmark-jump woman-find-file woman-dired-find-file
-;;;;;; woman woman-locale) "woman" "woman.el" (20370 35109))
+;;;;;; woman woman-locale) "woman" "woman.el" (20373 41604))
;;; Generated autoloads from woman.el
(defvar woman-locale nil "\
;;;***
\f
;;;### (autoloads (wordstar-mode) "ws-mode" "emulation/ws-mode.el"
-;;;;;; (20355 10021))
+;;;;;; (20331 12564))
;;; Generated autoloads from emulation/ws-mode.el
(autoload 'wordstar-mode "ws-mode" "\
;;;***
\f
-;;;### (autoloads (xesam-search) "xesam" "net/xesam.el" (20374 32165))
+;;;### (autoloads (xesam-search) "xesam" "net/xesam.el" (20373 41604))
;;; Generated autoloads from net/xesam.el
(autoload 'xesam-search "xesam" "\
;;;***
\f
;;;### (autoloads (xml-parse-region xml-parse-file) "xml" "xml.el"
-;;;;;; (20378 29222))
+;;;;;; (20380 26775))
;;; Generated autoloads from xml.el
(autoload 'xml-parse-file "xml" "\
;;;***
\f
;;;### (autoloads (xmltok-get-declared-encoding-position) "xmltok"
-;;;;;; "nxml/xmltok.el" (20355 10021))
+;;;;;; "nxml/xmltok.el" (20244 35516))
;;; Generated autoloads from nxml/xmltok.el
(autoload 'xmltok-get-declared-encoding-position "xmltok" "\
;;;***
\f
-;;;### (autoloads (xterm-mouse-mode) "xt-mouse" "xt-mouse.el" (20355
-;;;;;; 10021))
+;;;### (autoloads (xterm-mouse-mode) "xt-mouse" "xt-mouse.el" (20244
+;;;;;; 35516))
;;; Generated autoloads from xt-mouse.el
(defvar xterm-mouse-mode nil "\
;;;***
\f
;;;### (autoloads (yenc-extract-filename yenc-decode-region) "yenc"
-;;;;;; "gnus/yenc.el" (20355 10021))
+;;;;;; "gnus/yenc.el" (20244 35516))
;;; Generated autoloads from gnus/yenc.el
(autoload 'yenc-decode-region "yenc" "\
;;;***
\f
;;;### (autoloads (psychoanalyze-pinhead apropos-zippy insert-zippyism
-;;;;;; yow) "yow" "play/yow.el" (20364 42504))
+;;;;;; yow) "yow" "play/yow.el" (20373 41604))
;;; Generated autoloads from play/yow.el
(autoload 'yow "yow" "\
;;;***
\f
-;;;### (autoloads (zone) "zone" "play/zone.el" (20392 31071))
+;;;### (autoloads (zone) "zone" "play/zone.el" (20428 57510))
;;; Generated autoloads from play/zone.el
(autoload 'zone "zone" "\
;;;;;; "cedet/srecode/loaddefs.el" "cedet/srecode/map.el" "cedet/srecode/mode.el"
;;;;;; "cedet/srecode/semantic.el" "cedet/srecode/srt-wy.el" "cedet/srecode/srt.el"
;;;;;; "cedet/srecode/table.el" "cedet/srecode/template.el" "cedet/srecode/texi.el"
-;;;;;; "cus-dep.el" "dframe.el" "dired-aux.el" "dired-x.el" "dos-fns.el"
-;;;;;; "dos-vars.el" "dos-w32.el" "dynamic-setting.el" "emacs-lisp/authors.el"
-;;;;;; "emacs-lisp/avl-tree.el" "emacs-lisp/bindat.el" "emacs-lisp/byte-opt.el"
-;;;;;; "emacs-lisp/chart.el" "emacs-lisp/cl-extra.el" "emacs-lisp/cl-loaddefs.el"
-;;;;;; "emacs-lisp/cl-macs.el" "emacs-lisp/cl-seq.el" "emacs-lisp/cust-print.el"
-;;;;;; "emacs-lisp/eieio-base.el" "emacs-lisp/eieio-custom.el" "emacs-lisp/eieio-datadebug.el"
-;;;;;; "emacs-lisp/eieio-opt.el" "emacs-lisp/eieio-speedbar.el"
-;;;;;; "emacs-lisp/eieio.el" "emacs-lisp/find-gc.el" "emacs-lisp/gulp.el"
-;;;;;; "emacs-lisp/lisp-mnt.el" "emacs-lisp/package-x.el" "emacs-lisp/regi.el"
-;;;;;; "emacs-lisp/smie.el" "emacs-lisp/tcover-ses.el" "emacs-lisp/tcover-unsafep.el"
-;;;;;; "emulation/cua-gmrk.el" "emulation/cua-rect.el" "emulation/edt-lk201.el"
-;;;;;; "emulation/edt-mapper.el" "emulation/edt-pc.el" "emulation/edt-vt100.el"
-;;;;;; "emulation/tpu-extras.el" "emulation/viper-cmd.el" "emulation/viper-ex.el"
-;;;;;; "emulation/viper-init.el" "emulation/viper-keym.el" "emulation/viper-macs.el"
-;;;;;; "emulation/viper-mous.el" "emulation/viper-util.el" "erc/erc-backend.el"
-;;;;;; "erc/erc-goodies.el" "erc/erc-ibuffer.el" "erc/erc-lang.el"
-;;;;;; "eshell/em-alias.el" "eshell/em-banner.el" "eshell/em-basic.el"
-;;;;;; "eshell/em-cmpl.el" "eshell/em-dirs.el" "eshell/em-glob.el"
-;;;;;; "eshell/em-hist.el" "eshell/em-ls.el" "eshell/em-pred.el"
-;;;;;; "eshell/em-prompt.el" "eshell/em-rebind.el" "eshell/em-script.el"
-;;;;;; "eshell/em-smart.el" "eshell/em-term.el" "eshell/em-unix.el"
-;;;;;; "eshell/em-xtra.el" "eshell/esh-arg.el" "eshell/esh-cmd.el"
-;;;;;; "eshell/esh-ext.el" "eshell/esh-groups.el" "eshell/esh-io.el"
-;;;;;; "eshell/esh-module.el" "eshell/esh-opt.el" "eshell/esh-proc.el"
-;;;;;; "eshell/esh-util.el" "eshell/esh-var.el" "ezimage.el" "foldout.el"
-;;;;;; "format-spec.el" "fringe.el" "generic-x.el" "gnus/compface.el"
-;;;;;; "gnus/gnus-async.el" "gnus/gnus-bcklg.el" "gnus/gnus-cite.el"
-;;;;;; "gnus/gnus-cus.el" "gnus/gnus-demon.el" "gnus/gnus-dup.el"
-;;;;;; "gnus/gnus-eform.el" "gnus/gnus-ems.el" "gnus/gnus-int.el"
-;;;;;; "gnus/gnus-logic.el" "gnus/gnus-mh.el" "gnus/gnus-salt.el"
-;;;;;; "gnus/gnus-score.el" "gnus/gnus-setup.el" "gnus/gnus-srvr.el"
-;;;;;; "gnus/gnus-topic.el" "gnus/gnus-undo.el" "gnus/gnus-util.el"
-;;;;;; "gnus/gnus-uu.el" "gnus/gnus-vm.el" "gnus/gssapi.el" "gnus/ietf-drums.el"
-;;;;;; "gnus/legacy-gnus-agent.el" "gnus/mail-parse.el" "gnus/mail-prsvr.el"
-;;;;;; "gnus/mail-source.el" "gnus/mailcap.el" "gnus/messcompat.el"
-;;;;;; "gnus/mm-bodies.el" "gnus/mm-decode.el" "gnus/mm-util.el"
-;;;;;; "gnus/mm-view.el" "gnus/mml-sec.el" "gnus/mml-smime.el" "gnus/nnagent.el"
-;;;;;; "gnus/nnbabyl.el" "gnus/nndir.el" "gnus/nndraft.el" "gnus/nneething.el"
-;;;;;; "gnus/nngateway.el" "gnus/nnheader.el" "gnus/nnimap.el" "gnus/nnir.el"
-;;;;;; "gnus/nnmail.el" "gnus/nnmaildir.el" "gnus/nnmairix.el" "gnus/nnmbox.el"
-;;;;;; "gnus/nnmh.el" "gnus/nnnil.el" "gnus/nnoo.el" "gnus/nnregistry.el"
-;;;;;; "gnus/nnrss.el" "gnus/nnspool.el" "gnus/nntp.el" "gnus/nnvirtual.el"
-;;;;;; "gnus/nnweb.el" "gnus/registry.el" "gnus/rfc1843.el" "gnus/rfc2045.el"
-;;;;;; "gnus/rfc2047.el" "gnus/rfc2104.el" "gnus/rfc2231.el" "gnus/rtree.el"
-;;;;;; "gnus/shr-color.el" "gnus/sieve-manage.el" "gnus/smime.el"
-;;;;;; "gnus/spam-stat.el" "gnus/spam-wash.el" "hex-util.el" "hfy-cmap.el"
-;;;;;; "ibuf-ext.el" "international/cp51932.el" "international/eucjp-ms.el"
-;;;;;; "international/fontset.el" "international/iso-ascii.el" "international/ja-dic-cnv.el"
+;;;;;; "cus-dep.el" "cus-load.el" "dframe.el" "dired-aux.el" "dired-x.el"
+;;;;;; "dos-fns.el" "dos-vars.el" "dos-w32.el" "dynamic-setting.el"
+;;;;;; "emacs-lisp/authors.el" "emacs-lisp/avl-tree.el" "emacs-lisp/bindat.el"
+;;;;;; "emacs-lisp/byte-opt.el" "emacs-lisp/chart.el" "emacs-lisp/cl-extra.el"
+;;;;;; "emacs-lisp/cl-loaddefs.el" "emacs-lisp/cl-macs.el" "emacs-lisp/cl-seq.el"
+;;;;;; "emacs-lisp/cl.el" "emacs-lisp/eieio-base.el" "emacs-lisp/eieio-custom.el"
+;;;;;; "emacs-lisp/eieio-datadebug.el" "emacs-lisp/eieio-opt.el"
+;;;;;; "emacs-lisp/eieio-speedbar.el" "emacs-lisp/eieio.el" "emacs-lisp/find-gc.el"
+;;;;;; "emacs-lisp/gulp.el" "emacs-lisp/lisp-mnt.el" "emacs-lisp/package-x.el"
+;;;;;; "emacs-lisp/regi.el" "emacs-lisp/smie.el" "emacs-lisp/tcover-ses.el"
+;;;;;; "emacs-lisp/tcover-unsafep.el" "emulation/cua-gmrk.el" "emulation/cua-rect.el"
+;;;;;; "emulation/edt-lk201.el" "emulation/edt-mapper.el" "emulation/edt-pc.el"
+;;;;;; "emulation/edt-vt100.el" "emulation/tpu-extras.el" "emulation/viper-cmd.el"
+;;;;;; "emulation/viper-ex.el" "emulation/viper-init.el" "emulation/viper-keym.el"
+;;;;;; "emulation/viper-macs.el" "emulation/viper-mous.el" "emulation/viper-util.el"
+;;;;;; "erc/erc-backend.el" "erc/erc-goodies.el" "erc/erc-ibuffer.el"
+;;;;;; "erc/erc-lang.el" "eshell/em-alias.el" "eshell/em-banner.el"
+;;;;;; "eshell/em-basic.el" "eshell/em-cmpl.el" "eshell/em-dirs.el"
+;;;;;; "eshell/em-glob.el" "eshell/em-hist.el" "eshell/em-ls.el"
+;;;;;; "eshell/em-pred.el" "eshell/em-prompt.el" "eshell/em-rebind.el"
+;;;;;; "eshell/em-script.el" "eshell/em-smart.el" "eshell/em-term.el"
+;;;;;; "eshell/em-unix.el" "eshell/em-xtra.el" "eshell/esh-arg.el"
+;;;;;; "eshell/esh-cmd.el" "eshell/esh-ext.el" "eshell/esh-groups.el"
+;;;;;; "eshell/esh-io.el" "eshell/esh-module.el" "eshell/esh-opt.el"
+;;;;;; "eshell/esh-proc.el" "eshell/esh-util.el" "eshell/esh-var.el"
+;;;;;; "ezimage.el" "finder-inf.el" "foldout.el" "format-spec.el"
+;;;;;; "fringe.el" "generic-x.el" "gnus/compface.el" "gnus/gnus-async.el"
+;;;;;; "gnus/gnus-bcklg.el" "gnus/gnus-cite.el" "gnus/gnus-cus.el"
+;;;;;; "gnus/gnus-demon.el" "gnus/gnus-dup.el" "gnus/gnus-eform.el"
+;;;;;; "gnus/gnus-ems.el" "gnus/gnus-int.el" "gnus/gnus-logic.el"
+;;;;;; "gnus/gnus-mh.el" "gnus/gnus-salt.el" "gnus/gnus-score.el"
+;;;;;; "gnus/gnus-setup.el" "gnus/gnus-srvr.el" "gnus/gnus-topic.el"
+;;;;;; "gnus/gnus-undo.el" "gnus/gnus-util.el" "gnus/gnus-uu.el"
+;;;;;; "gnus/gnus-vm.el" "gnus/gssapi.el" "gnus/ietf-drums.el" "gnus/legacy-gnus-agent.el"
+;;;;;; "gnus/mail-parse.el" "gnus/mail-prsvr.el" "gnus/mail-source.el"
+;;;;;; "gnus/mailcap.el" "gnus/messcompat.el" "gnus/mm-bodies.el"
+;;;;;; "gnus/mm-decode.el" "gnus/mm-util.el" "gnus/mm-view.el" "gnus/mml-sec.el"
+;;;;;; "gnus/mml-smime.el" "gnus/nnagent.el" "gnus/nnbabyl.el" "gnus/nndir.el"
+;;;;;; "gnus/nndraft.el" "gnus/nneething.el" "gnus/nngateway.el"
+;;;;;; "gnus/nnheader.el" "gnus/nnimap.el" "gnus/nnir.el" "gnus/nnmail.el"
+;;;;;; "gnus/nnmaildir.el" "gnus/nnmairix.el" "gnus/nnmbox.el" "gnus/nnmh.el"
+;;;;;; "gnus/nnnil.el" "gnus/nnoo.el" "gnus/nnregistry.el" "gnus/nnrss.el"
+;;;;;; "gnus/nnspool.el" "gnus/nntp.el" "gnus/nnvirtual.el" "gnus/nnweb.el"
+;;;;;; "gnus/registry.el" "gnus/rfc1843.el" "gnus/rfc2045.el" "gnus/rfc2047.el"
+;;;;;; "gnus/rfc2104.el" "gnus/rfc2231.el" "gnus/rtree.el" "gnus/shr-color.el"
+;;;;;; "gnus/sieve-manage.el" "gnus/smime.el" "gnus/spam-stat.el"
+;;;;;; "gnus/spam-wash.el" "hex-util.el" "hfy-cmap.el" "ibuf-ext.el"
+;;;;;; "international/cp51932.el" "international/eucjp-ms.el" "international/fontset.el"
+;;;;;; "international/iso-ascii.el" "international/ja-dic-cnv.el"
;;;;;; "international/ja-dic-utl.el" "international/ogonek.el" "international/uni-bidi.el"
;;;;;; "international/uni-category.el" "international/uni-combining.el"
;;;;;; "international/uni-comment.el" "international/uni-decimal.el"
;;;;;; "vc/ediff-ptch.el" "vc/ediff-vers.el" "vc/ediff-wind.el"
;;;;;; "vc/pcvs-info.el" "vc/pcvs-parse.el" "vc/pcvs-util.el" "vc/vc-dav.el"
;;;;;; "vcursor.el" "vt-control.el" "vt100-led.el" "w32-fns.el"
-;;;;;; "w32-vars.el" "x-dnd.el") (20424 38645 32667))
+;;;;;; "w32-vars.el" "x-dnd.el") (20451 34928 615251))
;;;***
\f