cl-lambda-list
cl-declarations-or-string
[&optional ("interactive" interactive)]
- def-body)))
+ def-body))
+ (indent 2))
(let* ((res (cl-transform-lambda (cons args body) name))
(form (list* 'defun name (cdr res))))
(if (car res) (list 'progn (car res) form) form)))
\(fn NAME ARGLIST [DOCSTRING] BODY...)"
(declare (debug
- (&define name cl-macro-list cl-declarations-or-string def-body)))
+ (&define name cl-macro-list cl-declarations-or-string def-body))
+ (indent 2))
(let* ((res (cl-transform-lambda (cons args body) name))
(form (list* 'defmacro name (cdr res))))
(if (car res) (list 'progn (car res) form) form)))
;;;###autoload
(defmacro destructuring-bind (args expr &rest body)
- (declare (debug (&define cl-macro-list def-form cl-declarations def-body)))
+ (declare (indent 2)
+ (debug (&define cl-macro-list def-form cl-declarations def-body)))
(let* ((bind-lets nil) (bind-forms nil) (bind-inits nil)
(bind-defs nil) (bind-block 'cl-none) (bind-enquote nil))
(cl-do-arglist (or args '(&aux)) expr)
If `eval' is in WHEN, BODY is evaluated when interpreted or at non-top-level.
\(fn (WHEN...) BODY...)"
- (declare (debug ((&rest &or "compile" "load" "eval") body)))
+ (declare (indent 1) (debug ((&rest &or "compile" "load" "eval") body)))
(if (and (fboundp 'cl-compiling-file) (cl-compiling-file)
(not cl-not-toplevel) (not (boundp 'for-effect))) ; horrible kludge
(let ((comp (or (memq 'compile when) (memq :compile-toplevel when)))
allowed only in the final clause, and matches if no other keys match.
Key values are compared by `eql'.
\n(fn EXPR (KEYLIST BODY...)...)"
- (declare (debug (form &rest (sexp body))))
+ (declare (indent 1) (debug (form &rest (sexp body))))
(let* ((temp (if (cl-simple-expr-p expr 3) expr (make-symbol "--cl-var--")))
(head-list nil)
(body (cons
"Like `case', but error if no case fits.
`otherwise'-clauses are not allowed.
\n(fn EXPR (KEYLIST BODY...)...)"
- (declare (debug case))
+ (declare (indent 1) (debug case))
(list* 'case expr (append clauses '((ecase-error-flag)))))
;;;###autoload
typecase returns nil. A TYPE of t or `otherwise' is allowed only in the
final clause, and matches if no other keys match.
\n(fn EXPR (TYPE BODY...)...)"
- (declare (debug (form &rest ([&or cl-type-spec "otherwise"] body))))
+ (declare (indent 1)
+ (debug (form &rest ([&or cl-type-spec "otherwise"] body))))
(let* ((temp (if (cl-simple-expr-p expr 3) expr (make-symbol "--cl-var--")))
(type-list nil)
(body (cons
"Like `typecase', but error if no case fits.
`otherwise'-clauses are not allowed.
\n(fn EXPR (TYPE BODY...)...)"
- (declare (debug typecase))
+ (declare (indent 1) (debug typecase))
(list* 'typecase expr (append clauses '((ecase-error-flag)))))
dynamically scoped: Only references to it within BODY will work. These
references may appear inside macro expansions, but not inside functions
called from BODY."
- (declare (debug (symbolp body)))
+ (declare (indent 1) (debug (symbolp body)))
(if (cl-safe-expr-p (cons 'progn body)) (cons 'progn body)
(list 'cl-block-wrapper
(list* 'catch (list 'quote (intern (format "--cl-block-%s--" name)))
returning RESULT from that form (or nil if RESULT is omitted).
This is compatible with Common Lisp, but note that `defun' and
`defmacro' do not create implicit blocks as they do in Common Lisp."
- (declare (debug (symbolp &optional form)))
+ (declare (indent 1) (debug (symbolp &optional form)))
(let ((name2 (intern (format "--cl-block-%s--" name))))
(list 'cl-block-throw (list 'quote name2) result)))
"The Common Lisp `do' loop.
\(fn ((VAR INIT [STEP])...) (END-TEST [RESULT...]) BODY...)"
- (declare (debug
+ (declare (indent 2)
+ (debug
((&rest &or symbolp (symbolp &optional form form))
(form body)
cl-declarations body)))
"The Common Lisp `do*' loop.
\(fn ((VAR INIT [STEP])...) (END-TEST [RESULT...]) BODY...)"
- (declare (debug do))
+ (declare (indent 2) (debug do))
(cl-expand-do-loop steps endtest body t))
(defun cl-expand-do-loop (steps endtest body star)
from OBARRAY.
\(fn (VAR [OBARRAY [RESULT]]) BODY...)"
- (declare (debug ((symbolp &optional form form) cl-declarations body)))
+ (declare (indent 1)
+ (debug ((symbolp &optional form form) cl-declarations body)))
;; Apparently this doesn't have an implicit block.
(list 'block nil
(list 'let (list (car spec))
;;;###autoload
(defmacro do-all-symbols (spec &rest body)
- (declare (debug ((symbolp &optional form) cl-declarations body)))
+ (declare (indent 1) (debug ((symbolp &optional form) cl-declarations body)))
(list* 'do-symbols (list (car spec) nil (cadr spec)) body))
second list (or made unbound if VALUES is shorter than SYMBOLS); then the
BODY forms are executed and their result is returned. This is much like
a `let' form, except that the list of symbols can be computed at run-time."
- (declare (debug (form form body)))
+ (declare (indent 2) (debug (form form body)))
(list 'let '((cl-progv-save nil))
(list 'unwind-protect
(list* 'progn (list 'cl-progv-before symbols values) body)
go back to their previous definitions, or lack thereof).
\(fn ((FUNC ARGLIST BODY...) ...) FORM...)"
- (declare (debug ((&rest (defun*)) cl-declarations body)))
+ (declare (indent 1) (debug ((&rest (defun*)) cl-declarations body)))
(list* 'letf*
(mapcar
(function
Unlike `flet', this macro is fully compliant with the Common Lisp standard.
\(fn ((FUNC ARGLIST BODY...) ...) FORM...)"
- (declare (debug flet))
+ (declare (indent 1) (debug flet))
(let ((vars nil) (sets nil) (cl-macro-environment cl-macro-environment))
(while bindings
;; Use `gensym' rather than `make-symbol'. It's important that
This is like `flet', but for macros instead of functions.
\(fn ((NAME ARGLIST BODY...) ...) FORM...)"
- (declare (debug
+ (declare (indent 1)
+ (debug
((&rest (&define name (&rest arg) cl-declarations-or-string
def-body))
cl-declarations body)))
by EXPANSION, and (setq NAME ...) will act like (setf EXPANSION ...).
\(fn ((NAME EXPANSION) ...) FORM...)"
- (declare (debug ((&rest (symbol sexp)) cl-declarations body)))
+ (declare (indent 1) (debug ((&rest (symbol sexp)) cl-declarations body)))
(if (cdr bindings)
(list 'symbol-macrolet
(list (car bindings)) (list* 'symbol-macrolet (cdr bindings) body))
The main visible difference is that lambdas inside BODY will create
lexical closures as in Common Lisp.
\n(fn BINDINGS BODY)"
- (declare (debug let))
+ (declare (indent 1) (debug let))
(let* ((cl-closure-vars cl-closure-vars)
(vars (mapcar (function
(lambda (x)
as in Common Lisp. This is similar to the behavior of `let*' in
Common Lisp.
\n(fn BINDINGS BODY)"
- (declare (debug let))
+ (declare (indent 1) (debug let))
(if (null bindings) (cons 'progn body)
(setq bindings (reverse bindings))
(while bindings
a synonym for (list A B C).
\(fn (SYM...) FORM BODY)"
- (declare (debug ((&rest symbolp) form body)))
+ (declare (indent 2) (debug ((&rest symbolp) form body)))
(let ((temp (make-symbol "--cl-var--")) (n -1))
(list* 'let* (cons (list temp form)
(mapcar (function
values. For compatibility, (values A B C) is a synonym for (list A B C).
\(fn (SYM...) FORM)"
- (declare (debug ((&rest symbolp) form)))
+ (declare (indent 1) (debug ((&rest symbolp) form)))
(cond ((null vars) (list 'progn form nil))
((null (cdr vars)) (list 'setq (car vars) (list 'car form)))
(t
(cons 'progn body))
;;;###autoload
(defmacro the (type form)
- (declare (debug (cl-type-spec form)))
+ (declare (indent 1) (debug (cl-type-spec form)))
form)
(defvar cl-proclaim-history t) ; for future compilers
the PLACE is not modified before executing BODY.
\(fn ((PLACE VALUE) ...) BODY...)"
- (declare (debug ((&rest (gate place &optional form)) body)))
+ (declare (indent 1) (debug ((&rest (gate place &optional form)) body)))
(if (and (not (cdr bindings)) (cdar bindings) (symbolp (caar bindings)))
(list* 'let bindings body)
(let ((lets nil) (sets nil)
the PLACE is not modified before executing BODY.
\(fn ((PLACE VALUE) ...) BODY...)"
- (declare (debug letf))
+ (declare (indent 1) (debug letf))
(if (null bindings)
(cons 'progn body)
(setq bindings (reverse bindings))
or any generalized variable allowed by `setf'.
\(fn FUNC PLACE ARGS...)"
- (declare (debug (function* place &rest form)))
+ (declare (indent 2) (debug (function* place &rest form)))
(let* ((method (cl-setf-do-modify place (cons 'list args)))
(rargs (cons (nth 2 method) args)))
(list 'let* (car method)
Like `callf', but PLACE is the second argument of FUNC, not the first.
\(fn FUNC ARG1 PLACE ARGS...)"
- (declare (debug (function* form place &rest form)))
+ (declare (indent 3) (debug (function* form place &rest form)))
(if (and (cl-safe-expr-p arg1) (cl-simple-expr-p place) (symbolp func))
(list 'setf place (list* func arg1 place args))
(let* ((method (cl-setf-do-modify place (cons 'list args)))
;;; Miscellaneous.
-;; Define data for indentation and edebug.
-(dolist (entry
- '(((defun* defmacro*) 2)
- ((function*) nil
- (&or symbolp ([&optional 'macro] 'lambda (&rest sexp) &rest form)))
- ((eval-when) 1 (sexp &rest form))
- ((declare) nil (&rest sexp))
- ((the) 1 (sexp &rest form))
- ((case ecase typecase etypecase) 1 (form &rest (sexp &rest form)))
- ((block return-from) 1 (sexp &rest form))
- ((return) nil (&optional form))
- ((do do*) 2 ((&rest &or symbolp (symbolp &optional form form))
- (form &rest form)
- &rest form))
- ((do-symbols) 1 ((symbolp form &optional form form) &rest form))
- ((do-all-symbols) 1 ((symbolp form &optional form) &rest form))
- ((psetq setf psetf) nil edebug-setq-form)
- ((progv) 2 (&rest form))
- ((flet labels macrolet) 1
- ((&rest (sexp sexp &rest form)) &rest form))
- ((symbol-macrolet lexical-let lexical-let*) 1
- ((&rest &or symbolp (symbolp form)) &rest form))
- ((multiple-value-bind) 2 ((&rest symbolp) &rest form))
- ((multiple-value-setq) 1 ((&rest symbolp) &rest form))
- ((incf decf remf pushnew shiftf rotatef) nil (&rest form))
- ((letf letf*) 1 ((&rest (&rest form)) &rest form))
- ((callf destructuring-bind) 2 (sexp form &rest form))
- ((callf2) 3 (sexp form form &rest form))
- ((loop) nil (&rest &or symbolp form))
- ((ignore-errors) 0 (&rest form))))
- (dolist (func (car entry))
- (put func 'lisp-indent-function (nth 1 entry))
- (put func 'lisp-indent-hook (nth 1 entry))
- (or (get func 'edebug-form-spec)
- (put func 'edebug-form-spec (nth 2 entry)))))
-
;; Autoload the other portions of the package.
;; We want to replace the basic versions of dolist, dotimes, declare below.
(fmakunbound 'dolist)