Doc fixes; mainly avoid duplicating arg
authorDave Love <fx@gnu.org>
Fri, 5 May 2000 20:01:01 +0000 (20:01 +0000)
committerDave Love <fx@gnu.org>
Fri, 5 May 2000 20:01:01 +0000 (20:01 +0000)
list in doc string.  Don't quote keyword symbols.

lisp/ChangeLog
lisp/emacs-lisp/cl-macs.el
lisp/emacs-lisp/cl-seq.el
lisp/emacs-lisp/cl.el

index 6fcfc31..7715ec5 100644 (file)
@@ -1,3 +1,10 @@
+2000-05-05  Dave Love  <fx@gnu.org>
+
+       * emacs-lisp/cl-macs.el: Doc fixes; mainly avoid duplicating arg
+       list in doc string.  Don't quote keyword symbols.
+       * emacs-lisp/cl.el: Likewise
+       * emacs-lisp/cl-seq.el: Likewise
+
 2000-05-05  Gerd Moellmann  <gerd@gnu.org>
 
        * abbrev.el (abbrev-mode): Make ARG optional.
index 50b5735..3dd8464 100644 (file)
@@ -127,7 +127,7 @@ and BODY is implicitly surrounded by (block NAME ...)."
     (if (car res) (list 'progn (car res) form) form)))
 
 (defmacro function* (func)
-  "(function* SYMBOL-OR-LAMBDA): introduce a function.
+  "Introduce a function.
 Like normal `function', except that if argument is a lambda form, its
 ARGLIST allows full Common Lisp conventions."
   (if (eq (car-safe func) 'lambda)
@@ -352,13 +352,13 @@ If `load' is in WHEN, BODY is evaluated when loaded after top-level compile.
 If `eval' is in WHEN, BODY is evaluated when interpreted or at non-top-level."
   (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)))
+      (let ((comp (or (memq 'compile when) (memq :compile-toplevel when)))
            (cl-not-toplevel t))
-       (if (or (memq 'load when) (memq ':load-toplevel when))
+       (if (or (memq 'load when) (memq :load-toplevel when))
            (if comp (cons 'progn (mapcar 'cl-compile-time-too body))
              (list* 'if nil nil body))
          (progn (if comp (eval (cons 'progn body))) nil)))
-    (and (or (memq 'eval when) (memq ':execute when))
+    (and (or (memq 'eval when) (memq :execute when))
         (cons 'progn body))))
 
 (defun cl-compile-time-too (form)
@@ -369,7 +369,7 @@ If `eval' is in WHEN, BODY is evaluated when interpreted or at non-top-level."
         (cons 'progn (mapcar 'cl-compile-time-too (cdr form))))
        ((eq (car-safe form) 'eval-when)
         (let ((when (nth 1 form)))
-          (if (or (memq 'eval when) (memq ':execute when))
+          (if (or (memq 'eval when) (memq :execute when))
               (list* 'eval-when (cons 'compile when) (cddr form))
             form)))
        (t (eval form) form)))
@@ -397,7 +397,7 @@ The result of the body appears to the compiler as a quoted constant."
 ;;; Conditional control structures.
 
 (defmacro case (expr &rest clauses)
-  "(case EXPR CLAUSES...): evals EXPR, chooses from CLAUSES on that value.
+  "Eval EXPR and choose from CLAUSES on that value.
 Each clause looks like (KEYLIST BODY...).  EXPR is evaluated and compared
 against each key in each KEYLIST; the corresponding BODY is evaluated.
 If no clause succeeds, case returns nil.  A single atom may be used in
@@ -430,12 +430,12 @@ Key values are compared by `eql'."
       (list 'let (list (list temp expr)) body))))
 
 (defmacro ecase (expr &rest clauses)
-  "(ecase EXPR CLAUSES...): like `case', but error if no case fits.
+  "Like `case', but error if no case fits.
 `otherwise'-clauses are not allowed."
   (list* 'case expr (append clauses '((ecase-error-flag)))))
 
 (defmacro typecase (expr &rest clauses)
-  "(typecase EXPR CLAUSES...): evals EXPR, chooses from CLAUSES on that value.
+  "Evals EXPR, chooses from CLAUSES on that value.
 Each clause looks like (TYPE BODY...).  EXPR is evaluated and, if it
 satisfies TYPE, the corresponding BODY is evaluated.  If no clause succeeds,
 typecase returns nil.  A TYPE of `t' or `otherwise' is allowed only in the
@@ -460,7 +460,7 @@ final clause, and matches if no other keys match."
       (list 'let (list (list temp expr)) body))))
 
 (defmacro etypecase (expr &rest clauses)
-  "(etypecase EXPR CLAUSES...): like `typecase', but error if no case fits.
+  "Like `typecase', but error if no case fits.
 `otherwise'-clauses are not allowed."
   (list* 'typecase expr (append clauses '((ecase-error-flag)))))
 
@@ -468,7 +468,7 @@ final clause, and matches if no other keys match."
 ;;; Blocks and exits.
 
 (defmacro block (name &rest body)
-  "(block NAME BODY...): define a lexically-scoped block named NAME.
+  "Define a lexically-scoped block named NAME.
 NAME may be any symbol.  Code inside the BODY forms can call `return-from'
 to jump prematurely out of the block.  This differs from `catch' and `throw'
 in two respects:  First, the NAME is an unevaluated symbol rather than a
@@ -502,19 +502,19 @@ called from BODY."
     (if cl-found (setcdr cl-found t)))
   (byte-compile-normal-call (cons 'throw (cdr cl-form))))
 
-(defmacro return (&optional res)
-  "(return [RESULT]): return from the block named nil.
+(defmacro return (&optional result)
+  "Return from the block named nil.
 This is equivalent to `(return-from nil RESULT)'."
-  (list 'return-from nil res))
+  (list 'return-from nil result))
 
-(defmacro return-from (name &optional res)
-  "(return-from NAME [RESULT]): return from the block named NAME.
+(defmacro return-from (name &optional result)
+  "Return from the block named NAME.
 This jump out to the innermost enclosing `(block NAME ...)' form,
 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."
   (let ((name2 (intern (format "--cl-block-%s--" name))))
-    (list 'cl-block-throw (list 'quote name2) res)))
+    (list 'cl-block-throw (list 'quote name2) result)))
 
 
 ;;; The "loop" macro.
@@ -1168,7 +1168,7 @@ before assigning any symbols SYM to the corresponding values."
 ;;; Binding control structures.
 
 (defmacro progv (symbols values &rest body)
-  "(progv SYMBOLS VALUES BODY...): bind SYMBOLS to VALUES dynamically in BODY.
+  "Bind SYMBOLS to VALUES dynamically in BODY.
 The forms SYMBOLS and VALUES are evaluated, and must evaluate to lists.
 Each SYMBOL in the first list is bound to the corresponding VALUE in the
 second list (or made unbound if VALUES is shorter than SYMBOLS); then the
@@ -1253,7 +1253,7 @@ by EXPANSION, and (setq NAME ...) will act like (setf EXPANSION ...)."
 
 (defvar cl-closure-vars nil)
 (defmacro lexical-let (bindings &rest body)
-  "(lexical-let BINDINGS BODY...): like `let', but lexically scoped.
+  "Like `let', but lexically scoped.
 The main visible difference is that lambdas inside BODY will create
 lexical closures as in Common Lisp."
   (let* ((cl-closure-vars cl-closure-vars)
@@ -1295,7 +1295,7 @@ lexical closures as in Common Lisp."
            ebody))))
 
 (defmacro lexical-let* (bindings &rest body)
-  "(lexical-let* BINDINGS BODY...): like `let*', but lexically scoped.
+  "Like `let*', but lexically scoped.
 The main visible difference is that lambdas inside BODY will create
 lexical closures as in Common Lisp."
   (if (null bindings) (cons 'progn body)
@@ -1528,7 +1528,7 @@ Example: (defsetf nth (n x) (v) (list 'setcar (list 'nthcdr n x) v))."
 (defsetf gethash (x h &optional d) (store) (list 'cl-puthash x store h))
 (defsetf nth (n x) (store) (list 'setcar (list 'nthcdr n x) store))
 (defsetf subseq (seq start &optional end) (new)
-  (list 'progn (list 'replace seq new ':start1 start ':end1 end) new))
+  (list 'progn (list 'replace seq new :start1 start :end1 end) new))
 (defsetf symbol-function fset)
 (defsetf symbol-plist setplist)
 (defsetf symbol-value set)
@@ -1819,7 +1819,7 @@ before assigning any PLACEs to the corresponding values."
                  (cl-setf-do-store (nth 1 method) (list 'cdr temp)))))))
 
 (defmacro remf (place tag)
-  "(remf PLACE TAG): remove TAG from property list PLACE.
+  "Remove TAG from property list PLACE.
 PLACE may be a symbol, or any generalized variable allowed by `setf'.
 The form returns true if TAG was found and removed, nil otherwise."
   (let* ((method (cl-setf-do-modify place t))
@@ -1978,7 +1978,7 @@ Like `callf', but PLACE is the second argument of FUNC, not the first."
                                       rargs)))))))
 
 (defmacro define-modify-macro (name arglist func &optional doc)
-  "(define-modify-macro NAME ARGLIST FUNC): define a `setf'-like modify macro.
+  "Define a `setf'-like modify macro.
 If NAME is called, it combines its PLACE argument with the other arguments
 from ARGLIST using FUNC: (define-modify-macro incf (&optional (n 1)) +)"
   (if (memq '&key arglist) (error "&key not allowed in define-modify-macro"))
@@ -2025,31 +2025,31 @@ copier, a `NAME-p' predicate, and setf-able `NAME-SLOT' accessors."
     (while opts
       (let ((opt (if (consp (car opts)) (caar opts) (car opts)))
            (args (cdr-safe (cl-pop opts))))
-       (cond ((eq opt ':conc-name)
+       (cond ((eq opt :conc-name)
               (if args
                   (setq conc-name (if (car args)
                                       (symbol-name (car args)) ""))))
-             ((eq opt ':constructor)
+             ((eq opt :constructor)
               (if (cdr args)
                   (cl-push args constrs)
                 (if args (setq constructor (car args)))))
-             ((eq opt ':copier)
+             ((eq opt :copier)
               (if args (setq copier (car args))))
-             ((eq opt ':predicate)
+             ((eq opt :predicate)
               (if args (setq predicate (car args))))
-             ((eq opt ':include)
+             ((eq opt :include)
               (setq include (car args)
                     include-descs (mapcar (function
                                            (lambda (x)
                                              (if (consp x) x (list x))))
                                           (cdr args))))
-             ((eq opt ':print-function)
+             ((eq opt :print-function)
               (setq print-func (car args)))
-             ((eq opt ':type)
+             ((eq opt :type)
               (setq type (car args)))
-             ((eq opt ':named)
+             ((eq opt :named)
               (setq named t))
-             ((eq opt ':initial-offset)
+             ((eq opt :initial-offset)
               (setq descs (nconc (make-list (car args) '(cl-skip-slot))
                                  descs)))
              (t
@@ -2140,7 +2140,7 @@ copier, a `NAME-p' predicate, and setf-able `NAME-SLOT' accessors."
                                   (list 'nth pos 'cl-x)))))) forms)
              (cl-push (cons accessor t) side-eff)
              (cl-push (list 'define-setf-method accessor '(cl-x)
-                            (if (cadr (memq ':read-only (cddr desc)))
+                            (if (cadr (memq :read-only (cddr desc)))
                                 (list 'error (format "%s is a read-only slot"
                                                      accessor))
                               (list 'cl-struct-setf-expander 'cl-x
@@ -2229,12 +2229,12 @@ copier, a `NAME-p' predicate, and setf-able `NAME-SLOT' accessors."
 
 ;;; Types and assertions.
 
-(defmacro deftype (name args &rest body)
-  "(deftype NAME ARGLIST BODY...): define NAME as a new data type.
+(defmacro deftype (name arglist &rest body)
+  "Define NAME as a new data type.
 The type name can then be used in `typecase', `check-type', etc."
   (list 'eval-when '(compile load eval)
        (cl-transform-function-property
-        name 'cl-deftype-handler (cons (list* '&cl-defs ''('*) args) body))))
+        name 'cl-deftype-handler (cons (list* '&cl-defs ''('*) arglist) body))))
 
 (defun cl-make-type-test (val type)
   (if (memq type '(character string-char)) (setq type '(integer 0 255)))
@@ -2404,7 +2404,7 @@ Otherwise, return result of last FORM."
 ;;; Compiler macros.
 
 (defmacro define-compiler-macro (func args &rest body)
-  "(define-compiler-macro FUNC ARGLIST BODY...): Define a compiler-only macro.
+  "Define a compiler-only macro.
 This is like `defmacro', but macro expansion occurs only if the call to
 FUNC is compiled (i.e., not interpreted).  Compiler macros should be used
 for optimizing the way calls to FUNC are compiled; the form returned by
@@ -2505,7 +2505,7 @@ surrounded by (block NAME ...)."
        (t form)))
 
 (define-compiler-macro member* (&whole form a list &rest keys)
-  (let ((test (and (= (length keys) 2) (eq (car keys) ':test)
+  (let ((test (and (= (length keys) 2) (eq (car keys) :test)
                   (cl-const-expr-val (nth 1 keys)))))
     (cond ((eq test 'eq) (list 'memq a list))
          ((eq test 'equal) (list 'member a list))
@@ -2527,7 +2527,7 @@ surrounded by (block NAME ...)."
          (t form))))
 
 (define-compiler-macro assoc* (&whole form a list &rest keys)
-  (let ((test (and (= (length keys) 2) (eq (car keys) ':test)
+  (let ((test (and (= (length keys) 2) (eq (car keys) :test)
                   (cl-const-expr-val (nth 1 keys)))))
     (cond ((eq test 'eq) (list 'assq a list))
          ((eq test 'equal) (list 'assoc a list))
@@ -2538,7 +2538,7 @@ surrounded by (block NAME ...)."
 
 (define-compiler-macro adjoin (&whole form a list &rest keys)
   (if (and (cl-simple-expr-p a) (cl-simple-expr-p list)
-          (not (memq ':key keys)))
+          (not (memq :key keys)))
       (list 'if (list* 'member* a list keys) list (list 'cons a list))
     form))
 
index eaac88a..90fba3c 100644 (file)
@@ -68,9 +68,9 @@
             (let* ((var (if (consp x) (car x) x))
                    (mem (list 'car (list 'cdr (list 'memq (list 'quote var)
                                                     'cl-keys)))))
-              (if (eq var ':test-not)
+              (if (eq var :test-not)
                   (setq mem (list 'and mem (list 'setq 'cl-test mem) t)))
-              (if (eq var ':if-not)
+              (if (eq var :if-not)
                   (setq mem (list 'and mem (list 'setq 'cl-if mem) t)))
               (list (intern
                      (format "cl-%s" (substring (symbol-name var) 1)))
@@ -139,7 +139,7 @@ Keywords supported:  :start :end :from-end :initial-value :key"
     (or (listp cl-seq) (setq cl-seq (append cl-seq nil)))
     (setq cl-seq (subseq cl-seq cl-start cl-end))
     (if cl-from-end (setq cl-seq (nreverse cl-seq)))
-    (let ((cl-accum (cond ((memq ':initial-value cl-keys) cl-initial-value)
+    (let ((cl-accum (cond ((memq :initial-value cl-keys) cl-initial-value)
                          (cl-seq (cl-check-key (cl-pop cl-seq)))
                          (t (funcall cl-func)))))
       (if cl-from-end
@@ -225,8 +225,8 @@ Keywords supported:  :test :test-not :key :count :start :end :from-end"
            (if cl-i
                (let ((cl-res (apply 'delete* cl-item (append cl-seq nil)
                                     (append (if cl-from-end
-                                                (list ':end (1+ cl-i))
-                                              (list ':start cl-i))
+                                                (list :end (1+ cl-i))
+                                              (list :start cl-i))
                                             cl-keys))))
                  (if (listp cl-seq) cl-res
                    (if (stringp cl-seq) (concat cl-res) (vconcat cl-res))))
@@ -249,8 +249,8 @@ Keywords supported:  :test :test-not :key :count :start :end :from-end"
                           (and (cdr cl-p)
                                (apply 'delete* cl-item
                                       (copy-sequence (cdr cl-p))
-                                      ':start 0 ':end (1- cl-end)
-                                      ':count (1- cl-count) cl-keys))))
+                                      :start 0 :end (1- cl-end)
+                                      :count (1- cl-count) cl-keys))))
                cl-seq))
          cl-seq)))))
 
@@ -259,14 +259,14 @@ Keywords supported:  :test :test-not :key :count :start :end :from-end"
 This is a non-destructive function; it makes a copy of SEQ if necessary
 to avoid corrupting the original SEQ.
 Keywords supported:  :key :count :start :end :from-end"
-  (apply 'remove* nil cl-list ':if cl-pred cl-keys))
+  (apply 'remove* nil cl-list :if cl-pred cl-keys))
 
 (defun remove-if-not (cl-pred cl-list &rest cl-keys)
   "Remove all items not satisfying PREDICATE in SEQ.
 This is a non-destructive function; it makes a copy of SEQ if necessary
 to avoid corrupting the original SEQ.
 Keywords supported:  :key :count :start :end :from-end"
-  (apply 'remove* nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'remove* nil cl-list :if-not cl-pred cl-keys))
 
 (defun delete* (cl-item cl-seq &rest cl-keys)
   "Remove all occurrences of ITEM in SEQ.
@@ -314,17 +314,15 @@ Keywords supported:  :test :test-not :key :count :start :end :from-end"
   "Remove all items satisfying PREDICATE in SEQ.
 This is a destructive function; it reuses the storage of SEQ whenever possible.
 Keywords supported:  :key :count :start :end :from-end"
-  (apply 'delete* nil cl-list ':if cl-pred cl-keys))
+  (apply 'delete* nil cl-list :if cl-pred cl-keys))
 
 (defun delete-if-not (cl-pred cl-list &rest cl-keys)
   "Remove all items not satisfying PREDICATE in SEQ.
 This is a destructive function; it reuses the storage of SEQ whenever possible.
 Keywords supported:  :key :count :start :end :from-end"
-  (apply 'delete* nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'delete* nil cl-list :if-not cl-pred cl-keys))
 
-(or (and (fboundp 'delete) (subrp (symbol-function 'delete)))
-    (defalias 'delete (function (lambda (x y) (delete* x y ':test 'equal)))))
-(defun remove (x y) (remove* x y ':test 'equal))
+(defun remove (x y) (remove* x y :test 'equal))
 (defun remq (x y) (if (memq x y) (delq x (copy-list y)) y))
 
 (defun remove-duplicates (cl-seq &rest cl-keys)
@@ -394,22 +392,22 @@ Keywords supported:  :test :test-not :key :count :start :end :from-end"
          (or cl-from-end
              (progn (cl-set-elt cl-seq cl-i cl-new)
                     (setq cl-i (1+ cl-i) cl-count (1- cl-count))))
-         (apply 'nsubstitute cl-new cl-old cl-seq ':count cl-count
-                ':start cl-i cl-keys))))))
+         (apply 'nsubstitute cl-new cl-old cl-seq :count cl-count
+                :start cl-i cl-keys))))))
 
 (defun substitute-if (cl-new cl-pred cl-list &rest cl-keys)
   "Substitute NEW for all items satisfying PREDICATE in SEQ.
 This is a non-destructive function; it makes a copy of SEQ if necessary
 to avoid corrupting the original SEQ.
 Keywords supported:  :key :count :start :end :from-end"
-  (apply 'substitute cl-new nil cl-list ':if cl-pred cl-keys))
+  (apply 'substitute cl-new nil cl-list :if cl-pred cl-keys))
 
 (defun substitute-if-not (cl-new cl-pred cl-list &rest cl-keys)
   "Substitute NEW for all items not satisfying PREDICATE in SEQ.
 This is a non-destructive function; it makes a copy of SEQ if necessary
 to avoid corrupting the original SEQ.
 Keywords supported:  :key :count :start :end :from-end"
-  (apply 'substitute cl-new nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'substitute cl-new nil cl-list :if-not cl-pred cl-keys))
 
 (defun nsubstitute (cl-new cl-old cl-seq &rest cl-keys)
   "Substitute NEW for OLD in SEQ.
@@ -447,13 +445,13 @@ Keywords supported:  :test :test-not :key :count :start :end :from-end"
   "Substitute NEW for all items satisfying PREDICATE in SEQ.
 This is a destructive function; it reuses the storage of SEQ whenever possible.
 Keywords supported:  :key :count :start :end :from-end"
-  (apply 'nsubstitute cl-new nil cl-list ':if cl-pred cl-keys))
+  (apply 'nsubstitute cl-new nil cl-list :if cl-pred cl-keys))
 
 (defun nsubstitute-if-not (cl-new cl-pred cl-list &rest cl-keys)
   "Substitute NEW for all items not satisfying PREDICATE in SEQ.
 This is a destructive function; it reuses the storage of SEQ whenever possible.
 Keywords supported:  :key :count :start :end :from-end"
-  (apply 'nsubstitute cl-new nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'nsubstitute cl-new nil cl-list :if-not cl-pred cl-keys))
 
 (defun find (cl-item cl-seq &rest cl-keys)
   "Find the first occurrence of ITEM in LIST.
@@ -466,13 +464,13 @@ Keywords supported:  :test :test-not :key :start :end :from-end"
   "Find the first item satisfying PREDICATE in LIST.
 Return the matching ITEM, or nil if not found.
 Keywords supported:  :key :start :end :from-end"
-  (apply 'find nil cl-list ':if cl-pred cl-keys))
+  (apply 'find nil cl-list :if cl-pred cl-keys))
 
 (defun find-if-not (cl-pred cl-list &rest cl-keys)
   "Find the first item not satisfying PREDICATE in LIST.
 Return the matching ITEM, or nil if not found.
 Keywords supported:  :key :start :end :from-end"
-  (apply 'find nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'find nil cl-list :if-not cl-pred cl-keys))
 
 (defun position (cl-item cl-seq &rest cl-keys)
   "Find the first occurrence of ITEM in LIST.
@@ -507,13 +505,13 @@ Keywords supported:  :test :test-not :key :start :end :from-end"
   "Find the first item satisfying PREDICATE in LIST.
 Return the index of the matching item, or nil if not found.
 Keywords supported:  :key :start :end :from-end"
-  (apply 'position nil cl-list ':if cl-pred cl-keys))
+  (apply 'position nil cl-list :if cl-pred cl-keys))
 
 (defun position-if-not (cl-pred cl-list &rest cl-keys)
   "Find the first item not satisfying PREDICATE in LIST.
 Return the index of the matching item, or nil if not found.
 Keywords supported:  :key :start :end :from-end"
-  (apply 'position nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'position nil cl-list :if-not cl-pred cl-keys))
 
 (defun count (cl-item cl-seq &rest cl-keys)
   "Count the number of occurrences of ITEM in LIST.
@@ -531,12 +529,12 @@ Keywords supported:  :test :test-not :key :start :end"
 (defun count-if (cl-pred cl-list &rest cl-keys)
   "Count the number of items satisfying PREDICATE in LIST.
 Keywords supported:  :key :start :end"
-  (apply 'count nil cl-list ':if cl-pred cl-keys))
+  (apply 'count nil cl-list :if cl-pred cl-keys))
 
 (defun count-if-not (cl-pred cl-list &rest cl-keys)
   "Count the number of items not satisfying PREDICATE in LIST.
 Keywords supported:  :key :start :end"
-  (apply 'count nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'count nil cl-list :if-not cl-pred cl-keys))
 
 (defun mismatch (cl-seq1 cl-seq2 &rest cl-keys)
   "Compare SEQ1 with SEQ2, return index of first mismatching element.
@@ -586,9 +584,9 @@ Keywords supported:  :test :test-not :key :start1 :end1 :start2 :end2 :from-end"
                    (setq cl-pos (cl-position cl-first cl-seq2
                                              cl-start2 cl-end2 cl-from-end))
                    (apply 'mismatch cl-seq1 cl-seq2
-                          ':start1 (1+ cl-start1) ':end1 cl-end1
-                          ':start2 (1+ cl-pos) ':end2 (+ cl-pos cl-len)
-                          ':from-end nil cl-keys))
+                          :start1 (1+ cl-start1) :end1 cl-end1
+                          :start2 (1+ cl-pos) :end2 (+ cl-pos cl-len)
+                          :from-end nil cl-keys))
          (if cl-from-end (setq cl-end2 cl-pos) (setq cl-start2 (1+ cl-pos))))
        (and (< cl-start2 cl-end2) cl-pos)))))
 
@@ -645,13 +643,13 @@ Keywords supported:  :test :test-not :key"
   "Find the first item satisfying PREDICATE in LIST.
 Return the sublist of LIST whose car matches.
 Keywords supported:  :key"
-  (apply 'member* nil cl-list ':if cl-pred cl-keys))
+  (apply 'member* nil cl-list :if cl-pred cl-keys))
 
 (defun member-if-not (cl-pred cl-list &rest cl-keys)
   "Find the first item not satisfying PREDICATE in LIST.
 Return the sublist of LIST whose car matches.
 Keywords supported:  :key"
-  (apply 'member* nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'member* nil cl-list :if-not cl-pred cl-keys))
 
 (defun cl-adjoin (cl-item cl-list &rest cl-keys)
   (if (cl-parsing-keywords (:key) t
@@ -677,12 +675,12 @@ Keywords supported:  :test :test-not :key"
 (defun assoc-if (cl-pred cl-list &rest cl-keys)
   "Find the first item whose car satisfies PREDICATE in LIST.
 Keywords supported:  :key"
-  (apply 'assoc* nil cl-list ':if cl-pred cl-keys))
+  (apply 'assoc* nil cl-list :if cl-pred cl-keys))
 
 (defun assoc-if-not (cl-pred cl-list &rest cl-keys)
   "Find the first item whose car does not satisfy PREDICATE in LIST.
 Keywords supported:  :key"
-  (apply 'assoc* nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'assoc* nil cl-list :if-not cl-pred cl-keys))
 
 (defun rassoc* (cl-item cl-alist &rest cl-keys)
   "Find the first item whose cdr matches ITEM in LIST.
@@ -699,12 +697,12 @@ Keywords supported:  :test :test-not :key"
 (defun rassoc-if (cl-pred cl-list &rest cl-keys)
   "Find the first item whose cdr satisfies PREDICATE in LIST.
 Keywords supported:  :key"
-  (apply 'rassoc* nil cl-list ':if cl-pred cl-keys))
+  (apply 'rassoc* nil cl-list :if cl-pred cl-keys))
 
 (defun rassoc-if-not (cl-pred cl-list &rest cl-keys)
   "Find the first item whose cdr does not satisfy PREDICATE in LIST.
 Keywords supported:  :key"
-  (apply 'rassoc* nil cl-list ':if-not cl-pred cl-keys))
+  (apply 'rassoc* nil cl-list :if-not cl-pred cl-keys))
 
 (defun union (cl-list1 cl-list2 &rest cl-keys)
   "Combine LIST1 and LIST2 using a set-union operation.
@@ -829,13 +827,13 @@ Keywords supported:  :test :test-not :key"
   "Substitute NEW for elements matching PREDICATE in TREE (non-destructively).
 Return a copy of TREE with all matching elements replaced by NEW.
 Keywords supported:  :key"
-  (apply 'sublis (list (cons nil cl-new)) cl-tree ':if cl-pred cl-keys))
+  (apply 'sublis (list (cons nil cl-new)) cl-tree :if cl-pred cl-keys))
 
 (defun subst-if-not (cl-new cl-pred cl-tree &rest cl-keys)
   "Substitute NEW for elts not matching PREDICATE in TREE (non-destructively).
 Return a copy of TREE with all non-matching elements replaced by NEW.
 Keywords supported:  :key"
-  (apply 'sublis (list (cons nil cl-new)) cl-tree ':if-not cl-pred cl-keys))
+  (apply 'sublis (list (cons nil cl-new)) cl-tree :if-not cl-pred cl-keys))
 
 (defun nsubst (cl-new cl-old cl-tree &rest cl-keys)
   "Substitute NEW for OLD everywhere in TREE (destructively).
@@ -848,13 +846,13 @@ Keywords supported:  :test :test-not :key"
   "Substitute NEW for elements matching PREDICATE in TREE (destructively).
 Any element of TREE which matches is changed to NEW (via a call to `setcar').
 Keywords supported:  :key"
-  (apply 'nsublis (list (cons nil cl-new)) cl-tree ':if cl-pred cl-keys))
+  (apply 'nsublis (list (cons nil cl-new)) cl-tree :if cl-pred cl-keys))
 
 (defun nsubst-if-not (cl-new cl-pred cl-tree &rest cl-keys)
   "Substitute NEW for elements not matching PREDICATE in TREE (destructively).
 Any element of TREE which matches is changed to NEW (via a call to `setcar').
 Keywords supported:  :key"
-  (apply 'nsublis (list (cons nil cl-new)) cl-tree ':if-not cl-pred cl-keys))
+  (apply 'nsublis (list (cons nil cl-new)) cl-tree :if-not cl-pred cl-keys))
 
 (defun sublis (cl-alist cl-tree &rest cl-keys)
   "Perform substitutions indicated by ALIST in TREE (non-destructively).
index 8d7c826..790e4c9 100644 (file)
@@ -123,7 +123,7 @@ Floating-point numbers of equal value are `eql', but they may not be `eq'."
 ;;; can safely be used in .emacs files.
 
 (defmacro incf (place &optional x)
-  "(incf PLACE [X]): increment PLACE by X (1 by default).
+  "Increment PLACE by X (1 by default).
 PLACE may be a symbol, or any generalized variable allowed by `setf'.
 The return value is the incremented value of PLACE."
   (if (symbolp place)
@@ -131,7 +131,7 @@ The return value is the incremented value of PLACE."
     (list 'callf '+ place (or x 1))))
 
 (defmacro decf (place &optional x)
-  "(decf PLACE [X]): decrement PLACE by X (1 by default).
+  "Decrement PLACE by X (1 by default).
 PLACE may be a symbol, or any generalized variable allowed by `setf'.
 The return value is the decremented value of PLACE."
   (if (symbolp place)
@@ -139,7 +139,7 @@ The return value is the decremented value of PLACE."
     (list 'callf '- place (or x 1))))
 
 (defmacro pop (place)
-  "(pop PLACE): remove and return the head of the list stored in PLACE.
+  "Remove and return the head of the list stored in PLACE.
 Analogous to (prog1 (car PLACE) (setf PLACE (cdr PLACE))), though more
 careful about evaluating each argument only once and in the right order.
 PLACE may be a symbol, or any generalized variable allowed by `setf'."
@@ -148,7 +148,7 @@ PLACE may be a symbol, or any generalized variable allowed by `setf'."
     (cl-do-pop place)))
 
 (defmacro push (x place)
-  "(push X PLACE): insert X at the head of the list stored in PLACE.
+  "Insert X at the head of the list stored in PLACE.
 Analogous to (setf PLACE (cons X PLACE)), though more careful about
 evaluating each argument only once and in the right order.  PLACE may
 be a symbol, or any generalized variable allowed by `setf'."