Don't write Lisp symbol names in uppercase: use `...' instead.
authorMark Wooding <mdw@distorted.org.uk>
Fri, 12 Jul 2013 01:24:21 +0000 (02:24 +0100)
committerMark Wooding <mdw@distorted.org.uk>
Fri, 12 Jul 2013 01:26:59 +0000 (02:26 +0100)
Otherwise it's too confusing to distinguish them from metavariables.

25 files changed:
src/c-types-class-impl.lisp
src/c-types-impl.lisp
src/c-types-parse.lisp
src/c-types-proto.lisp
src/c-types-test.lisp
src/class-layout-impl.lisp
src/class-make-proto.lisp
src/class-utilities.lisp
src/codegen-impl.lisp
src/codegen-proto.lisp
src/fragment-parse.lisp
src/lexer-bits.lisp
src/lexer-impl.lisp
src/lexer-proto.lisp
src/method-impl.lisp
src/method-proto.lisp
src/output-proto.lisp
src/parser/floc-proto.lisp
src/parser/parser-proto.lisp
src/parser/scanner-charbuf-impl.lisp
src/parser/streams-impl.lisp
src/parser/streams-proto.lisp
src/pset-parse.lisp
src/pset-proto.lisp
src/utilities.lisp

index de980d8..34c7eeb 100644 (file)
@@ -45,7 +45,7 @@
    The CLASS slot will be NIL if the class isn't defined yet, i.e., this
    entry was constructed by a forward reference operation.
 
-   The NAME slot inherited from SIMPLE-C-TYPE is here so that we can print
+   The NAME slot inherited from `simple-c-type' is here so that we can print
    the type even when it's a forward reference."))
 
 ;; Constructor function and interning.
 
 (export 'find-class-type)
 (defun find-class-type (name)
-  "Look up NAME and return the corresponding C-CLASS-TYPE.
+  "Look up NAME and return the corresponding `c-class-type'.
 
      * If the type was found, and was a class, returns TYPE.
 
-     * If no type was found at all, returns NIL.
+     * If no type was found at all, returns `nil'.
 
      * If a type was found, but it wasn't a class, signals an error."
 
 
 (export 'find-sod-class)
 (defun find-sod-class (name)
-  "Return the SOD-CLASS object with the given NAME."
+  "Return the `sod-class' object with the given NAME."
   (aif (find-class-type name)
        (or (c-type-class it) (error "Class `~A' is incomplete" name))
        (error "Type `~A' not known" name)))
index b37833a..7dd7b84 100644 (file)
   "Return whether LIST-A and LIST-B match.
 
    They must have the same number of arguments, and each argument must have
-   the same type, or be :ELLIPSIS.  The argument names are not inspected."
+   the same type, or be `:ellipsis'.  The argument names are not inspected."
   (and (= (length list-a) (length list-b))
        (every (lambda (arg-a arg-b)
                (if (eq arg-a :ellipsis)
 (defun commentify-argument-names (arguments)
   "Return an argument list with the arguments commentified.
 
-   That is, with each argument name passed through COMMENTIFY-ARGUMENT-NAME."
+   That is, with each argument name passed through
+   `commentify-argument-name'."
   (mapcar (lambda (arg)
            (if (eq arg :ellipsis)
                arg
index ba6bf6f..a3ecae4 100644 (file)
              (setf (gethash name map) ds
                    (gethash label map) ds))))))
     map)
-  "Maps symbolic labels and textual names to DECLSPEC instances.")
+  "Maps symbolic labels and textual names to `declspec' instances.")
 
 ;; A collection of declaration specifiers, and how to merge them together.
 
     we'll just have to live with that.
 
     (Why are instances immutable?  Because it's much easier to merge a new
-    specifier into an existing collection, and then check that the resulting
-    thing is valid rather than having to deal with all of the possible
+    specifier into an existing collection and then check that the resulting
+    thing is valid, rather than having to deal with all of the possible
     special cases of what the new thing might be.  And if the merged
     collection isn't good, I must roll back to the previous version.  So I
     don't get to take advantage of a mutable structure.)"))
 
 (defun scan-declspec
     (scanner &key (predicate (constantly t)) (indicator :declspec))
-  "Scan a DECLSPEC from SCANNER.
+  "Scan a `declspec' from SCANNER.
 
    If PREDICATE is provided then only succeed if (funcall PREDICATE DECLSPEC)
    is true, where DECLSPEC is the raw declaration specifier or C-type object,
index bc36b2e..9481a99 100644 (file)
 (defun c-type-space (stream)
   "Print a space and a miser-mode newline to STREAM.
 
-   This is the right function to call in a PPRINT-C-TYPE kernel function when
-   the SPACEP argument is true."
+   This is the right function to call in a `pprint-c-type' kernel function
+   when the SPACEP argument is true."
   (pprint-indent :block 2 stream)
   (write-char #\space stream)
   (pprint-newline :miser stream))
 
 (defun maybe-in-parens* (stream condition thunk)
-  "Helper function for the MAYBE-IN-PARENS macro."
+  "Helper function for the `maybe-in-parens' macro."
   (multiple-value-bind (prefix suffix)
       (if condition (values "(" ")") (values "" ""))
     (pprint-logical-block (stream nil :prefix prefix :suffix suffix)
 (defmacro maybe-in-parens ((stream condition) &body body)
   "Evaluate BODY; if CONDITION, write parens to STREAM around it.
 
-   This macro is useful for implementing the PPRINT-C-TYPE method on compound
-   types.  The BODY is evaluated in the context of a logical block printing
-   to STREAM.  If CONDITION is non-nil, then the block will have open/close
-   parens as its prefix and suffix; otherwise they will be empty.
+   This macro is useful for implementing the `pprint-c-type' method on
+   compound types.  The BODY is evaluated in the context of a logical block
+   printing to STREAM.  If CONDITION is non-nil, then the block will have
+   open/close parens as its prefix and suffix; otherwise they will be empty.
 
-   The STREAM is passed to PPRINT-LOGICAL-BLOCK, so it must be a symbol."
+   The STREAM is passed to `pprint-logical-block', so it must be a symbol."
   `(maybe-in-parens* ,stream ,condition (lambda (,stream) ,@body)))
 
 (export 'format-qualifiers)
   (:documentation
    "Print an abbreviated syntax for TYPE to the STREAM.
 
-   This function is suitable for use in FORMAT's ~/.../ command."))
+   This function is suitable for use in `format's ~/.../ command."))
 
 (export 'expand-c-type-spec)
 (eval-when (:compile-toplevel :load-toplevel :execute)
 
 (export 'c-type)
 (defmacro c-type (spec)
-  "Expands to code to construct a C type, using EXPAND-C-TYPE-SPEC."
+  "Expands to code to construct a C type, using `expand-c-type-spec'."
   (expand-c-type-spec spec))
 
 (export 'define-c-type-syntax)
   "Define a C-type syntax function.
 
    A function defined by BODY and with lambda-list BVL is associated with the
-   NAME.  When EXPAND-C-TYPE sees a list (NAME . STUFF), it will call this
+   NAME.  When `expand-c-type' sees a list (NAME . STUFF), it will call this
    function with the argument list STUFF."
   (with-gensyms (head tail)
     (multiple-value-bind (doc decls body) (parse-body body)
   "Define NAMES all to describe the C-type VALUE.
 
    NAMES can be a symbol (treated as a singleton list), or a list of symbols.
-   The VALUE is a C type S-expression, acceptable to EXPAND-C-TYPE.  It will
-   be expanded once at run-time."
+   The VALUE is a C type S-expression, acceptable to `expand-c-type'.  It
+   will be expanded once at run-time."
   (let* ((names (if (listp names) names (list names)))
         (namevar (gensym "NAME"))
         (typevar (symbolicate 'c-type- (car names))))
index 0c6a8b7..f1e4324 100644 (file)
                   "ftw"
                   (format nil "~
 int ftw(const char */*dirpath*/,
-        int (*/*fn*/)(const char *fpath,
-                      const struct stat *sb,
-                      int typeflag),
-        int /*nopenfd*/)")))
+       int (*/*fn*/)(const char *fpath,
+                     const struct stat *sb,
+                     int typeflag),
+       int /*nopenfd*/)")))
 
 ;;;----- That's all, folks --------------------------------------------------
index 4bff54d..2e66fa1 100644 (file)
@@ -58,7 +58,7 @@
    (prepare-function :initarg :prepare-function :type (or symbol function)
                     :reader sod-slot-prepare-function))
   (:documentation
-   "Special class for slots defined on SodClass.
+   "Special class for slots defined on `SodClass'.
 
    These slots need class-specific initialization.  It's easier to keep all
    of the information (name, type, and how to initialize them) about these
@@ -80,7 +80,7 @@
    (prepare-function :initarg :prepare-function :type (or symbol function)
                     :reader effective-slot-prepare-function))
   (:documentation
-   "Special class for slots defined on SodClass.
+   "Special class for slots defined on `SodClass'.
 
    This class ignores any explicit initializers and computes initializer
    values using the slot's INIT-FUNC slot and a magical protocol during
index 692da40..0a633de 100644 (file)
    `sod-class'.  All of the arguments are then passed to `make-instance';
    further behaviour is left to the standard CLOS instance construction
    protocol; for example, `sod-class' defines an `:after'-method on
-   SHARED-INITIALIZE.
+   `shared-initialize'.
 
    Minimal sanity checking is done during class construction; most of it is
-   left for FINALIZE-SOD-CLASS to do (via CHECK-SOD-CLASS).
+   left for `finalize-sod-class' to do (via `check-sod-class').
 
    Unused properties in PSET are diagnosed as errors."
 
index 62f27d8..491671d 100644 (file)
 
    The root superclass is the superclass which itself has no direct
    superclasses.  In universes not based on the provided builtin module, the
-   root class may not be our beloved SodObject; however, there must be one
+   root class may not be our beloved `SodObject'; however, there must be one
    (otherwise the class graph is cyclic, which should be forbidden), and we
    insist that it be unique."
 
index 25413f8..2b23661 100644 (file)
   (:documentation
    "Base class for code generator state.
 
-   This contains the bare essentials for supporting the EMIT-INST and
-   ENSURE-VAR protocols; see the documentation for those generic functions
+   This contains the bare essentials for supporting the `emit-inst' and
+   `ensure-var' protocols; see the documentation for those generic functions
    for more details.
 
-   This class isn't abstract.  A full CODEGEN object uses instances of this
+   This class isn't abstract.  A full `codegen' object uses instances of this
    to keep track of pending functions which haven't been completed yet.
 
    Just in case that wasn't clear enough: this is nothing to do with the
 
    This is the real deal.  Subclasses may which to attach additional state
    for convenience's sake, but this class is self-contained.  It supports the
-   CODEGEN-PUSH, CODEGEN-POP and CODEGEN-POP-FUNCTION protocols."))
+   `codegen-push', `codegen-pop' and `codegen-pop-function' protocols."))
 
 (defmethod codegen-push ((codegen codegen))
   (with-slots (vars insts temp-index stack) codegen
index 24b8c38..4b3b49d 100644 (file)
 (export 'var-in-use-p)
 (defgeneric var-in-use-p (var)
   (:documentation
-   "Answer whether VAR is currently being used.  See WITH-TEMPORARY-VAR.")
+   "Answer whether VAR is currently being used.  See `with-temporary-var'.")
   (:method (var)
     "Non-temporary variables are always in use."
     t))
 (defgeneric (setf var-in-use-p) (value var)
   (:documentation
-   "Record whether VAR is currently being used.  See WITH-TEMPORARY-VAR."))
+   "Record whether VAR is currently being used.  See `with-temporary-var'."))
 
 ;; Root class.
 
 
    An `instruction' is anything which might be useful to string into a code
    generator.  Both statements and expressions map can be represented by
-   trees of instructions.  The DEFINST macro is a convenient way of defining
-   new instructions.
+   trees of instructions.  The `definst' macro is a convenient way of
+   defining new instructions.
 
    The only important protocol for instructions is output, which is achieved
-   by calling PRINT-OBJECT with *PRINT-ESCAPE* nil.
+   by calling `print-object' with `*print-escape*' nil.
 
    This doesn't really do very much, but it acts as a handy marker for
    instruction subclasses."))
   (:documentation
    "Returns a `metric' describing how complicated INST is.
 
-   The default metric of an inst node is simply 1; INST subclasses generated
-   by DEFINST (q.v.) have an automatically generated method which returns one
-   plus the sum of the metrics of the node's children.
+   The default metric of an inst node is simply 1; `inst' subclasses
+   generated by `definst' (q.v.) have an automatically generated method which
+   returns one plus the sum of the metrics of the node's children.
 
    This isn't intended to be a particularly rigorous definition.  Its purpose
    is to allow code generators to make decisions about inlining or calling
 (defmacro definst (code (streamvar) args &body body)
   "Define an instruction type and describe how to output it.
 
-   An INST can represent any structured piece of output syntax: a statement,
-   expression or declaration, for example.  This macro defines the following
-   things:
+   An `inst' can represent any structured piece of output syntax: a
+   statement, expression or declaration, for example.  This macro defines the
+   following things:
 
-     * A class CODE-INST to represent the instruction.
+     * A class `CODE-inst' to represent the instruction.
 
      * Instance slots named after the ARGS, with matching keyword initargs,
-       and INST-ARG readers.
+       and `inst-ARG' readers.
 
-     * A constructor MAKE-CODE-INST which accepts the ARGS (in order, not
+     * A constructor `make-CODE-inst' which accepts the ARGS (in order, not
        with keywords) as arguments and returns a fresh instance.
 
-     * A print method, which prints a diagnostic dump if *PRINT-ESCAPE* is
+     * A print method, which prints a diagnostic dump if `*print-escape*' is
        set, or invokes the BODY (with STREAMVAR bound to the output stream)
        otherwise.  The BODY is expected to produce target code at this
        point."
 ;; Formatting utilities.
 
 (defun format-compound-statement* (stream child morep thunk)
-  "Underlying function for FORMAT-COMPOUND-STATEMENT."
+  "Underlying function for `format-compound-statement'."
   (cond ((typep child 'block-inst)
         (funcall thunk stream)
         (write-char #\space stream)
   "Format a compound statement to STREAM.
 
    The introductory material is printed by BODY.  The CHILD is formatted
-   properly according to whether it's a BLOCK-INST.  If MOREP is true, then
+   properly according to whether it's a `block-inst'.  If MOREP is true, then
    allow for more stuff following the child."
   `(format-compound-statement* ,stream ,child ,morep
                               (lambda (,stream) ,@body)))
 (export 'codegen-functions)
 (defgeneric codegen-functions (codegen)
   (:documentation
-   "Return the list of FUNCTION-INSTs of completed functions."))
+   "Return the list of `function-inst's of completed functions."))
 
 (export 'ensure-var)
 (defgeneric ensure-var (codegen name type &optional init)
   (:documentation
    "Add a variable to CODEGEN's list.
 
-   The variable is called NAME (which should be comparable using EQUAL and
+   The variable is called NAME (which should be comparable using `equal' and
    print to an identifier) and has the given TYPE.  If INIT is present and
-   non-nil it is an expression INST used to provide the variable with an
+   non-nil it is an expression `inst' used to provide the variable with an
    initial value."))
 
 (export '(emit-inst emit-insts))
    "Adds a function to CODEGEN's list.
 
    Actually, we're not picky: FUNCTION can be any kind of object that you're
-   willing to find in the list returned by CODEGEN-FUNCTIONS."))
+   willing to find in the list returned by `codegen-functions'."))
 
 (export 'temporary-var)
 (defgeneric temporary-var (codegen type)
 
    The temporary variable will have the given TYPE, and will be marked
    in-use.  You should clear the in-use flag explicitly when you've finished
-   with the variable -- or, better, use WITH-TEMPORARY-VAR to do the cleanup
-   automatically."))
+   with the variable -- or, better, use `with-temporary-var' to do the
+   cleanup automatically."))
 
 (export 'codegen-build-function)
 (defun codegen-build-function (codegen name type vars insts)
 (export 'codegen-pop-block)
 (defgeneric codegen-pop-block (codegen)
   (:documentation
-   "Makes a block (BLOCK-INST) out of the completed code in CODEGEN.")
+   "Makes a block (`block-inst') out of the completed code in CODEGEN.")
   (:method (codegen)
     (multiple-value-bind (vars insts) (codegen-pop codegen)
       (make-block-inst vars insts))))
 
    The TARGET may be one of the following.
 
-     * :VOID, indicating that the value is to be discarded.  The expression
+     * `:void', indicating that the value is to be discarded.  The expression
        will still be evaluated.
 
-     * :VOID-RETURN, indicating that the value is to be discarded (as for
-       :VOID) and furthermore a `return' from the current function should be
-       forced after computing the value.
+     * `:void-return', indicating that the value is to be discarded (as for
+       `:void') and furthermore a `return' from the current function should
+       be forced after computing the value.
 
-     * :RETURN, indicating that the value is to be returned from the current
-       function.
+     * `:return', indicating that the value is to be returned from the
+       current function.
 
      * A variable name, indicating that the value is to be stored in the
        variable.
 
-   In the cases of :RETURN, :VOID and :VOID-RETURN targets, it is valid for
-   EXPR to be nil; this signifies that no computation needs to be performed.
-   Variable-name targets require an expression."
+   In the cases of `:return', `:void' and `:void-return' targets, it is valid
+   for EXPR to be nil; this signifies that no computation needs to be
+   performed.  Variable-name targets require an expression."
 
   (case target
     (:return (emit-inst codegen (make-return-inst expr)))
 
 (export 'convert-stmts)
 (defun convert-stmts (codegen target type func)
-  "Invoke FUNC to deliver a value to a non-:RETURN target.
+  "Invoke FUNC to deliver a value to a non-`:return' target.
 
-   FUNC is a function which accepts a single argument, a non-:RETURN target,
-   and generates statements which deliver a value (see DELIVER-EXPR) of the
-   specified TYPE to this target.  In general, the generated code will have
-   the form
+   FUNC is a function which accepts a single argument, a non-`:return'
+   target, and generates statements which deliver a value (see
+   `deliver-expr') of the specified TYPE to this target.  In general, the
+   generated code will have the form
 
      setup instructions...
-     (DELIVER-EXPR CODEGEN TARGET (compute value...))
+     (deliver-expr CODEGEN TARGET (compute value...))
      cleanup instructions...
 
    where the cleanup instructions are essential to the proper working of the
    generated program.
 
-   CONVERT-STMTS will call FUNC to generate code, and arrange that its value
-   is correctly delivered to TARGET, regardless of what the TARGET is --
-   i.e., it lifts the restriction to non-:RETURN targets.  It does this by
-   inventing a new temporary variable."
+   The `convert-stmts' function will call FUNC to generate code, and arrange
+   that its value is correctly delivered to TARGET, regardless of what the
+   TARGET is -- i.e., it lifts the restriction to non-`:return' targets.  It
+   does this by inventing a new temporary variable."
 
   (case target
     (:return (with-temporary-var (codegen var type)
index 5f58885..6e71994 100644 (file)
   "Parse a C fragment delimited by BEGIN and END.
 
    The BEGIN and END arguments are characters.  (Currently, BEGIN can be any
-  token type, but you probably shouldn't rely on this.)"
+   token type, but you probably shouldn't rely on this.)"
 
   ;; This is decidedly nasty.  The basic problem is that `scan-c-fragment'
   ;; works at the character level rather than at the lexical level, and if we
index daa533c..b671164 100644 (file)
@@ -27,7 +27,7 @@
         ;; Pick out comments.
         ((peek (and #\/ #\*))
          (parse (skip-many ()          ; this may fail at eof; don't worry
-                  (and (skip-many () (not #\*))
+                  (and (skip-many () (not #\*))
                        (skip-many (:min 1) #\*))
                   (not #\/)))
          (if-parse :eof ()
index 9f9d31e..03a6bcc 100644 (file)
    "Base class for lexical analysers.
 
    The lexer reads characters from STREAM, which, for best results, wants to
-   be a POSITION-AWARE-INPUT-STREAM.
+   be a `position-aware-input-stream'.
 
    The lexer provides one-character lookahead by default: the current
    lookahead character is available to subclasses in the slot CHAR.  Before
    beginning lexical analysis, the lookahead character needs to be
-   established with NEXT-CHAR.  If one-character lookahead is insufficient,
+   established with `next-char'.  If one-character lookahead is insufficient,
    the analyser can push back an arbitrary number of characters using
-   PUSHBACK-CHAR.
+   `pushback-char'.
 
-   The NEXT-TOKEN function scans and returns the next token from the STREAM,
-   and makes it available as TOKEN-TYPE and TOKEN-VALUE, providing one-token
-   lookahead.  A parser using the lexical analyser can push back tokens using
-   PUSHBACK-TOKENS.
+   The `next-token' function scans and returns the next token from the
+   STREAM, and makes it available as TOKEN-TYPE and TOKEN-VALUE, providing
+   one-token lookahead.  A parser using the lexical analyser can push back
+   tokens using `pushback-tokens'.
 
-   For convenience, the lexer implements a FILE-LOCATION method (delegated to
-   the underlying stream)."))
+   For convenience, the lexer implements a `file-location' method (delegated
+   to the underlying stream)."))
 
 ;;; Reading and pushing back characters.
 
   (:documentation
    "Lexical analyser for the SOD lanuage.
 
-   See the LEXER class for the gory details about the lexer protocol."))
+   See the `lexer' class for the gory details about the lexer protocol."))
 
 (defmethod scan-token ((lexer sod-lexer))
   (with-slots (stream char keywords location) lexer
index 5f7a9af..8e0c889 100644 (file)
    "Return the current lookahead character from the LEXER.
 
    When the lexer is first created, there is no lookahead character: you must
-   `prime the pump' by calling NEXT-CHAR.  The lexer represents encountering
-   the end of its input stream by setting the lookahead character to nil.  At
-   this point it is still possible to push back characters."))
+   `prime the pump' by calling `next-char'.  The lexer represents
+   encountering the end of its input stream by setting the lookahead
+   character to nil.  At this point it is still possible to push back
+   characters."))
 
 ;;;--------------------------------------------------------------------------
 ;;; Formatting tokens.
@@ -95,9 +96,9 @@
 
 (defgeneric fixup-stream* (lexer thunk)
   (:documentation
-   "Helper function for WITH-LEXER-STREAM.
+   "Helper function for `with-lexer-stream'.
 
-   This function does the main work for WITH-LEXER-STREAM.  The THUNK is
+   This function does the main work for `with-lexer-stream'.  The THUNK is
    invoked on a single argument, the LEXER's underlying STREAM."))
 
 (export 'with-lexer-stream)
   "Evaluate BODY with STREAMVAR bound to the LEXER's input stream.
 
    The STREAM is fixed up so that the next character read (e.g., using
-   READ-CHAR) will be the lexer's current lookahead character.  Once the BODY
-   completes, the next character in the stream is read and set as the
+   `read-char') will be the lexer's current lookahead character.  Once the
+   BODY completes, the next character in the stream is read and set as the
    lookahead character.  It is an error if the lexer has pushed-back
    characters (since these can't be pushed back into the input stream
    properly)."
    "Internal protocol for scanning tokens from an input stream.
 
    Implementing a method on this function is the main responsibility of LEXER
-   subclasses; it is called by the user-facing NEXT-TOKEN function.
+   subclasses; it is called by the user-facing `next-token' function.
 
-   The method should consume characters (using NEXT-CHAR) as necessary, and
+   The method should consume characters (using `next-char') as necessary, and
    return two values: a token type and token value.  These will be stored in
    the corresponding slots in the lexer object in order to provide the user
    with one-token lookahead."))
    determining the syntax of the input, while the token value carries any
    additional information about the token's semantic content.  The token type
    and token value are also made available for lookahead via accessors
-   TOKEN-TYPE and TOKEN-VALUE on the LEXER object.
+   TOKEN-TYPE and TOKEN-VALUE on the `lexer' object.
 
    The new lookahead token type and value are returned as two separate
    values.
 
-   If tokens have been pushed back (see PUSHBACK-TOKEN) then they are
+   If tokens have been pushed back (see `pushback-token') then they are
    returned one by one instead of scanning the stream."))
 
 (export 'pushback-token)
    Make the given TOKEN-TYPE and TOKEN-VALUE be the current lookahead token.
    The previous lookahead token is pushed down, and will be made available
    agan once this new token is consumed by NEXT-TOKEN.  If LOCATION is
-   non-nil then FILE-LOCATION is saved and replaced by LOCATION.  The
+   non-nil then `file-location' is saved and replaced by LOCATION.  The
    TOKEN-TYPE and TOKEN-VALUE can be anything at all: for instance, they need
    not be values which can actually be returned by NEXT-TOKEN."))
 
     (lexer wanted-token-type &key (errorp t) (consumep t) default)
   "Require a particular token to appear.
 
-   If the LEXER's current lookahead token has type WANTED-TOKEN-TYPE then
-   consume it (using NEXT-TOKEN) and return its value.  Otherwise, if the
+   If the LEXER's current lookahead token has type `wanted-token-type' then
+   consume it (using `next-token') and return its value.  Otherwise, if the
    token doesn't have the requested type then signal a continuable error
    describing the situation and return DEFAULT (which defaults to nil).
 
index b9045ce..b74994f 100644 (file)
@@ -82,9 +82,9 @@
    "Base class for messages with `simple' method combinations.
 
    A simple method combination is one which has only one method role other
-   than the `before', `after' and `around' methods provided by BASIC-MESSAGE.
-   We call these `primary' methods, and the programmer designates them by not
-   specifying an explicit role.
+   than the `before', `after' and `around' methods provided by
+   `basic-message'.  We call these `primary' methods, and the programmer
+   designates them by not specifying an explicit role.
 
    If the programmer doesn't define any primary methods then the effective
    method is null -- i.e., the method entry pointer shows up as a null
index 8909fc9..a3e9b65 100644 (file)
   (:documentation
    "Return the argument tail for the message with `:ellipsis' substituted.
 
-   As with SOD-MESSAGE-ARGUMENT-TAIL, no `me' argument is prepended.
-   However, an :ELLIPSIS is replaced by an argument of type `va_list', named
-   `sod__ap'."))
+   As with `sod-message-argument-tail', no `me' argument is prepended.
+   However, an `:ellipsis' is replaced by an argument of type `va_list',
+   named `sod__ap'."))
 
 (export 'sod-method-function-type)
 (defgeneric sod-method-function-type (method)
index 1630de6..af293ee 100644 (file)
@@ -48,7 +48,7 @@
   (:documentation
    "A sequencer tracks items and invokes them in the proper order.
 
-   The job of a SEQUENCER object is threefold.  Firstly, it collects
+   The job of a `sequencer' object is threefold.  Firstly, it collects
    sequencer items and stores them in its table indexed by name.  Secondly,
    it gathers CONSTRAINTS, which impose an ordering on the items.  Thirdly,
    it can be instructed to invoke the items in an order compatible with the
@@ -72,7 +72,7 @@
    "Attach the given CONSTRAINT to an SEQUENCER.
 
    The CONSTRAINT should be a list of sequencer-item names; see
-   ENSURE-SEQUENCER-ITEM for what they look like.  Note that the names
+   `ensure-sequencer-item' for what they look like.  Note that the names
    needn't have been declared in advance; indeed, they needn't be mentioned
    anywhere else at all."))
 
@@ -85,9 +85,9 @@
    They are called in the same order in which they were added.
 
    Note that an item must be mentioned in at least one constraint in order to
-   be traversed by INVOKE-SEQUENCER-ITEMS.  If there are no special ordering
-   requirments for a particular item, then the trivial constraint (NAME) will
-   suffice."))
+   be traversed by `invoke-sequencer-items'.  If there are no special
+   ordering requirments for a particular item, then the trivial
+   constraint (NAME) will suffice."))
 
 (export 'invoke-sequencer-items)
 (defgeneric invoke-sequencer-items (sequencer &rest arguments)
   (:documentation
    "Announces the intention to write SEQUENCER, with a particular REASON.
 
-   The SEQUENCER is an SEQUENCER instance; the REASON will be a symbol which
-   can be matched using an EQL-specializer.  In response, OBJECT should add
+   The SEQUENCER is a `sequencer' instance; the REASON will be a symbol which
+   can be matched using an `eql'-specializer.  In response, OBJECT should add
    any constraints and item functions that it wishes, and pass the
    announcement to its sub-objects.  It is not uncommon for an object to pass
    a reason to its sub-objects that is different from the REASON with which
index 9e246ab..1a50841 100644 (file)
                                    (pathname (namestring %filename)))))))
   "A simple structure containing file location information.
 
-   Construct using MAKE-FILE-LOCATION; the main useful function is
-   ERROR-FILE-LOCATION."
+   Construct using `make-file-location'; the main useful function is
+   `error-file-location'."
   (filename nil :type (or string null) :read-only t)
   (line nil :type (or fixnum null) :read-only t)
   (column nil :type (or fixnum null) :read-only t))
 
 (defgeneric file-location (thing)
   (:documentation
-   "Convert THING into a FILE-LOCATION, if possible.
+   "Convert THING into a `file-location', if possible.
 
-   A THING which can be converted into a FILE-LOCATION is termed a
+   A THING which can be converted into a `file-location' is termed a
    `file-location designator'.")
   (:method ((thing file-location)) thing))
 
@@ -65,7 +65,7 @@
 
    This is useful if one wants to attach additional information to an
    existing condition.  The enclosed condition can be obtained using the
-   ENCLOSED-CONDITION function.")
+   `enclosed-condition' function.")
   (:report (lambda (condition stream)
             (princ (enclosed-condition condition) stream))))
 
 
 (export 'make-condition-with-location)
 (defun make-condition-with-location (default-type floc datum &rest arguments)
-  "Construct a CONDITION-WITH-LOCATION given a condition designator.
+  "Construct a `condition-with-location' given a condition designator.
 
-   The returned condition will always be a CONDITION-WITH-LOCATION.  The
+   The returned condition will always be a `condition-with-location'.  The
    process consists of two stages.  In the first stage, a condition is
    constructed from the condition designator DATUM and ARGUMENTS with default
    type DEFAULT-TYPE (a symbol).  The precise behaviour depends on DATUM:
      * If DATUM is a symbol, then it must name a condition type.  An instance
        of this class is constructed using ARGUMENTS as initargs, i.e., as
        if (apply #'make-condition ARGUMENTS); if the type is a subtype of
-       CONDITION-WITH-LOCATION then FLOC is attached as the location.
+       `condition-with-location' then FLOC is attached as the location.
 
      * If DATUM is a format control (i.e., a string or function), then the
        condition is constructed as if, instead, DEFAULT-TYPE had been
        :format-arguments ARGUMENTS) supplied as ARGUMENTS.
 
    In the second stage, the condition constructed by the first stage is
-   converted into a CONDITION-WITH-LOCATION.  If the condition already has
-   type CONDITION-WITH-LOCATION then it is returned as is.  Otherwise it is
-   wrapped in an appropriate subtype of ENCLOSING-CONDITION-WITH-LOCATION:
+   converted into a `condition-with-location'.  If the condition already has
+   type `condition-with-location' then it is returned as is.  Otherwise it is
+   wrapped in an appropriate subtype of `enclosing-condition-with-location':
    if the condition was a subtype of ERROR or WARNING then the resulting
    condition will also be subtype of ERROR or WARNING as appropriate."
 
    other conditions) which do not have file location information attached to
    them already.
 
-   See the WITH-DEFAULT-ERROR-LOCATION macro for more details."
+   See the `with-default-error-location' macro for more details."
 
   (if floc
       (handler-bind
    attaches FLOC to errors (and other conditions) which do not have file
    location information attached to them already.
 
-   If a condition other than a CONDITION-WITH-LOCATION is signalled during
+   If a condition other than a `condition-with-location' is signalled during
    the evaluation of the BODY, then an instance of an appropriate subcalass
-   of ENCLOSING-CONDITION-WITH-LOCATION is constructed, enclosing the
+   of `enclosing-condition-with-location' is constructed, enclosing the
    original condition, and signalled.  In particular, if the original
    condition was a subtype of ERROR or WARNING, then the new condition will
    also be a subtype of ERROR or WARNING as appropriate.
 
-   The FLOC argument is coerced to a FILE-LOCATION object each time a
+   The FLOC argument is coerced to a `file-location' object each time a
    condition is signalled.  For example, if FLOC is a lexical analyser object
-   which reports its current position in response to FILE-LOCATION, then each
-   condition will be reported as arising at the lexer's current position at
-   that time, rather than all being reported at the same position.
+   which reports its current position in response to `file-location', then
+   each condition will be reported as arising at the lexer's current position
+   at that time, rather than all being reported at the same position.
 
    If the new enclosing condition is not handled, the handler established by
    this macro will decline to handle the original condition.  Typically,
-   however, the new condition will be handled by COUNT-AND-REPORT-ERRORS.
+   however, the new condition will be handled by `count-and-report-errors'.
 
    As a special case, if FLOC is nil, then no special action is taken, and
    BODY is simply evaluated, as an implicit progn."
 (defun count-and-report-errors* (thunk)
   "Invoke THUNK in a dynamic environment which traps and reports errors.
 
-   See the COUNT-AND-REPORT-ERRORS macro for more detais."
+   See the `count-and-report-errors' macro for more detais."
 
   (let ((errors 0)
        (warnings 0))
 
    The BODY is evaluated.  If an error or warning is signalled, it is
    reported (using its report function), and counted.  Warnings are otherwise
-   muffled; continuable errors (i.e., when a CONTINUE restart is defined) are
-   continued; non-continuable errors cause an immediate exit from the BODY.
+   muffled; continuable errors (i.e., when a `continue' restart is defined)
+   are continued; non-continuable errors cause an immediate exit from the
+   BODY.
 
    The final value consists of three values: the primary value of the BODY
-   (or NIL if a non-continuable error occurred), the number of errors
+   (or nil if a non-continuable error occurred), the number of errors
    reported, and the number of warnings reported."
   `(count-and-report-errors* (lambda () ,@body)))
 
index 5a10b77..879db4c 100644 (file)
 
 (export 'list)
 (defparse list ((&rest keys) parser &optional (sep nil sepp))
-  "Like MANY, but simply returns a list of the parser results."
+  "Like `many', but simply returns a list of the parser results."
   (with-gensyms (acc)
     `(parse (many (,acc nil (cons it ,acc) :final (nreverse ,acc) ,@keys)
              ,parser ,@(and sepp (list sep))))))
 
 (export 'skip-many)
 (defparse skip-many ((&rest keys) parser &optional (sep nil sepp))
-  "Like MANY, but ignores the results."
+  "Like `many', but ignores the results."
   `(parse (many (nil nil nil ,@keys)
            ,parser ,@(and sepp (list sep)))))
 
index 2d7a4ae..9cafc3d 100644 (file)
    and wishes to read more.  If DONEP is true then the condition (<= START
    USED END) must hold; the FUNC has consumed the buffer as far as USED
    (exclusive) and has completed successfully; the values DONEP and `t' are
-   returned as the result of CHARBUF-SCANNER-MAP.
+   returned as the result of `charbuf-scanner-map'.
 
    If end-of-file is encountered before FUNC completes successfully then FAIL
-   is called with no arguments, and CHARBUF-SCANNER-MAP returns whatever
+   is called with no arguments, and `charbuf-scanner-map' returns whatever
    FAIL returns.
 
    Observe that, if FAIL returns a second value of nil, then
                                                    :index index))))
         (last-link (charbuf-scanner-place-link place-b)))
     (flet ((bad ()
-            (error "Incorrect places ~S and ~S to SCANNER-INTERVAL."
+            (error "Incorrect places ~S and ~S to `scanner-interval'."
                    place-a place-b)))
       (do ((link (charbuf-scanner-place-link place-a)
                 (charbuf-chain-link-next link))
index 6094b56..d62429a 100644 (file)
    character increases the line number by one and resets the column number to
    zero; most characters advance the column number by one, but tab advances
    to the next multiple of eight.  (This is consistent with Emacs, at least.)
-   The position can be read using STREAM-LINE-AND-COLUMN.
+   The position can be read using `stream-line-and-column'.
 
-   This is a base class; you probably want POSITION-AWARE-INPUT-STREAM or
-   POSITION-AWARE-OUTPUT-STREAM."))
+   This is a base class; you probably want `position-aware-input-stream' or
+   `position-aware-output-stream'."))
 
 (defgeneric stream-line-and-column (stream)
   (:documentation
       (values line column))))
 
 (defmethod stream-pathname ((stream position-aware-stream))
-  "Return the pathname corresponding to a POSITION-AWARE-STREAM.
+  "Return the pathname corresponding to a `position-aware-stream'.
 
-   A POSITION-AWARE-STREAM can be given an explicit pathname, which is
+   A `position-aware-stream' can be given an explicit pathname, which is
    returned in preference to the pathname of the underlying stream.  This is
    useful in two circumstances.  Firstly, the pathname associated with a file
-   stream will have been subjected to TRUENAME, and may be less pleasant to
+   stream will have been subjected to `truename', and may be less pleasant to
    present back to a user.  Secondly, a name can be attached to a stream
    which doesn't actually have a file backing it."
 
 
    The position is actually cached in local variables, but will be written
    back to the stream even in the case of non-local control transfer from the
-   BODY.  What won't work well is dynamically nesting WITH-POSITION forms."
+   BODY.  What won't work well is dynamically nesting `with-position' forms."
 
   (with-gensyms (line column char)
     (once-only (stream)
index bcce02a..141d0bc 100644 (file)
@@ -34,7 +34,7 @@
    "Returns the pathname of the file that STREAM is open on.
 
    If STREAM is open on a file, then return the pathname of that file.
-   Otherwise return NIL.")
+   Otherwise return nil.")
 
   ;; Provide some default methods.  Most streams don't have a pathname.
   ;; File-based streams provide a pathname, but it's usually been merged with
index a38f44b..d1e437e 100644 (file)
@@ -96,7 +96,6 @@
                             (t
                              (values (list :int :id :char :string #\?)
                                      nil nil)))))
-                  
 
 (defun parse-property (scanner pset)
   "Parse a single property using the SCANNER; add it to the PSET."
index d4dc614..e10e8b9 100644 (file)
    the value and its file location.  In the latter case, mark the property as
    having been used.
 
-   The value returned depends on the TYPE argument provided.  If you pass NIL
-   then you get back the entire PROPERTY object.  If you pass `t', then you
-   get whatever was left in the property set, uninterpreted.  Otherwise the
-   value is coerced to the right kind of thing (where possible) and returned.
+   The value returned depends on the TYPE argument provided.  If you pass
+   `nil' then you get back the entire `property' object.  If you pass `t',
+   then you get whatever was left in the property set, uninterpreted.
+   Otherwise the value is coerced to the right kind of thing (where possible)
+   and returned.
 
    If PSET is nil, then return DEFAULT."
 
 
    An attempt is made to guess property types from the Lisp types of the
    values.  This isn't always successful but it's not too bad.  The
-   alternative is manufacturing a PROPERTY-VALUE object by hand and stuffing
-   into the set."
+   alternative is manufacturing a `property-value' object by hand and
+   stuffing into the set."
 
   (property-set plist))
 
index 5c061bb..aabc067 100644 (file)
    the input LISTS in the sense that if A precedes B in some input list then
    A will also precede B in the output list.  If the lists aren't consistent
    (e.g., some list contains A followed by B, and another contains B followed
-   by A) then an error of type INCONSISTENT-MERGE-ERROR is signalled.
+   by A) then an error of type `inconsistent-merge-error' is signalled.
 
    Item equality is determined by TEST.
 
 (defun symbolicate (&rest symbols)
   "Return a symbol named after the concatenation of the names of the SYMBOLS.
 
-   The symbol is interned in the current *PACKAGE*.  Trad."
+   The symbol is interned in the current `*package*'.  Trad."
   (intern (apply #'concatenate 'string (mapcar #'symbol-name symbols))))
 
 ;;;--------------------------------------------------------------------------
     ((object stream &rest args) &body body)
   "Print helper for usually-unreadable objects.
 
-   If *PRINT-ESCAPE* is set then print OBJECT unreadably using BODY.
+   If `*print-escape*' is set then print OBJECT unreadably using BODY.
    Otherwise just print using BODY."
   (with-gensyms (print)
     `(flet ((,print () ,@body))