0.9.10.4: better CONSTANTP
[sbcl.git] / src / code / reader.lisp
1 ;;;; READ and friends
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!IMPL")
13 \f
14 ;;;; miscellaneous global variables
15
16 ;;; ANSI: "the floating-point format that is to be used when reading a
17 ;;; floating-point number that has no exponent marker or that has e or
18 ;;; E for an exponent marker"
19 (defvar *read-default-float-format* 'single-float)
20 (declaim (type (member short-float single-float double-float long-float)
21                *read-default-float-format*))
22
23 (defvar *readtable*)
24 (declaim (type readtable *readtable*))
25 #!+sb-doc
26 (setf (fdocumentation '*readtable* 'variable)
27        "Variable bound to current readtable.")
28
29 ;;; a standard Lisp readtable. This is for recovery from broken
30 ;;; read-tables (and for WITH-STANDARD-IO-SYNTAX), and should not
31 ;;; normally be user-visible.
32 (defvar *standard-readtable*)
33
34 (defvar *old-package* nil
35   #!+sb-doc
36   "the value of *PACKAGE* at the start of the last read, or NIL")
37
38 ;;; In case we get an error trying to parse a symbol, we want to rebind the
39 ;;; above stuff so it's cool.
40
41 ;;; FIXME: These forward declarations should be moved somewhere earlier,
42 ;;; or discarded.
43 (declaim (special *package* *keyword-package* *read-base*))
44 \f
45 ;;;; reader errors
46
47 (defun reader-eof-error (stream context)
48   (error 'reader-eof-error
49          :stream stream
50          :context context))
51
52 (defun %reader-error (stream control &rest args)
53   (error 'reader-error
54          :stream stream
55          :format-control control
56          :format-arguments args))
57 \f
58 ;;;; macros and functions for character tables
59
60 ;;; FIXME: could be SB!XC:DEFMACRO inside EVAL-WHEN (COMPILE EVAL)
61 (defmacro get-cat-entry (char rt)
62   ;; KLUDGE: Only give this side-effect-free args.
63   ;; FIXME: should probably become inline function
64   `(if (typep ,char 'base-char)
65        (elt (character-attribute-array ,rt) (char-code ,char))
66        (gethash ,char (character-attribute-hash-table ,rt)
67         +char-attr-constituent+)))
68
69 (defun set-cat-entry (char newvalue &optional (rt *readtable*))
70   (if (typep char 'base-char)
71       (setf (elt (character-attribute-array rt) (char-code char)) newvalue)
72       ;; FIXME: could REMHASH if we're setting to
73       ;; +CHAR-ATTR-CONSTITUENT+
74       (setf (gethash char (character-attribute-hash-table rt)) newvalue)))
75
76 ;;; the value actually stored in the character macro table. As per
77 ;;; ANSI #'GET-MACRO-CHARACTER and #'SET-MACRO-CHARACTER, this can
78 ;;; be either a function or NIL.
79 (eval-when (:compile-toplevel :execute)
80   (sb!xc:defmacro get-raw-cmt-entry (char readtable)
81     `(if (typep ,char 'base-char)
82          (svref (character-macro-array ,readtable) (char-code ,char))
83          ;; Note: DEFAULT here is NIL, not #'UNDEFINED-MACRO-CHAR, so
84          ;; that everything above the base-char range is a non-macro
85          ;; constituent by default.
86          (gethash ,char (character-macro-hash-table ,readtable) nil))))
87
88 ;;; the value represented by whatever is stored in the character macro
89 ;;; table. As per ANSI #'GET-MACRO-CHARACTER and #'SET-MACRO-CHARACTER,
90 ;;; a function value represents itself, and a NIL value represents the
91 ;;; default behavior.
92 (defun get-coerced-cmt-entry (char readtable)
93   (the function
94     (or (get-raw-cmt-entry char readtable)
95         #'read-token)))
96
97 (defun set-cmt-entry (char new-value-designator &optional (rt *readtable*))
98   (if (typep char 'base-char)
99       (setf (svref (character-macro-array rt) (char-code char))
100             (and new-value-designator
101                  (%coerce-callable-to-fun new-value-designator)))
102       (setf (gethash char (character-macro-hash-table rt))
103         (and new-value-designator
104                  (%coerce-callable-to-fun new-value-designator)))))
105
106 (defun undefined-macro-char (stream char)
107   (unless *read-suppress*
108     (%reader-error stream "undefined read-macro character ~S" char)))
109
110 ;;; The character attribute table is a CHAR-CODE-LIMIT vector of integers.
111
112 (defmacro test-attribute (char whichclass rt)
113   `(= (the fixnum (get-cat-entry ,char ,rt)) ,whichclass))
114
115 ;;; predicates for testing character attributes
116
117 ;;; the [1] and [2] here refer to ANSI glossary entries for
118 ;;; "whitespace".
119 #!-sb-fluid (declaim (inline whitespace[1]p whitespace[2]p))
120 (defun whitespace[1]p (char)
121   (test-attribute char +char-attr-whitespace+ *standard-readtable*))
122 (defun whitespace[2]p (char &optional (rt *readtable*))
123   (test-attribute char +char-attr-whitespace+ rt))
124
125 (defmacro constituentp (char &optional (rt '*readtable*))
126   `(test-attribute ,char +char-attr-constituent+ ,rt))
127
128 (defmacro terminating-macrop (char &optional (rt '*readtable*))
129   `(test-attribute ,char +char-attr-terminating-macro+ ,rt))
130
131 (defmacro single-escape-p (char &optional (rt '*readtable*))
132   `(test-attribute ,char +char-attr-single-escape+ ,rt))
133
134 (defmacro multiple-escape-p (char &optional (rt '*readtable*))
135   `(test-attribute ,char +char-attr-multiple-escape+ ,rt))
136
137 (defmacro token-delimiterp (char &optional (rt '*readtable*))
138   ;; depends on actual attribute numbering above.
139   `(<= (get-cat-entry ,char ,rt) +char-attr-terminating-macro+))
140 \f
141 ;;;; constituent traits (see ANSI 2.1.4.2)
142
143 ;;; There are a number of "secondary" attributes which are constant
144 ;;; properties of characters (as long as they are constituents).
145
146 (defvar *constituent-trait-table*)
147 (declaim (type attribute-table *constituent-trait-table*))
148
149 (defun !set-constituent-trait (char trait)
150   (aver (typep char 'base-char))
151   (setf (elt *constituent-trait-table* (char-code char))
152         trait))
153
154 (defun !cold-init-constituent-trait-table ()
155   (setq *constituent-trait-table*
156         (make-array base-char-code-limit :element-type '(unsigned-byte 8)
157                     :initial-element +char-attr-constituent+))
158   (!set-constituent-trait #\: +char-attr-package-delimiter+)
159   (!set-constituent-trait #\. +char-attr-constituent-dot+)
160   (!set-constituent-trait #\+ +char-attr-constituent-sign+)
161   (!set-constituent-trait #\- +char-attr-constituent-sign+)
162   (!set-constituent-trait #\/ +char-attr-constituent-slash+)
163   (do ((i (char-code #\0) (1+ i)))
164       ((> i (char-code #\9)))
165     (!set-constituent-trait (code-char i) +char-attr-constituent-digit+))
166   (!set-constituent-trait #\E +char-attr-constituent-expt+)
167   (!set-constituent-trait #\F +char-attr-constituent-expt+)
168   (!set-constituent-trait #\D +char-attr-constituent-expt+)
169   (!set-constituent-trait #\S +char-attr-constituent-expt+)
170   (!set-constituent-trait #\L +char-attr-constituent-expt+)
171   (!set-constituent-trait #\e +char-attr-constituent-expt+)
172   (!set-constituent-trait #\f +char-attr-constituent-expt+)
173   (!set-constituent-trait #\d +char-attr-constituent-expt+)
174   (!set-constituent-trait #\s +char-attr-constituent-expt+)
175   (!set-constituent-trait #\l +char-attr-constituent-expt+)
176   (!set-constituent-trait #\Space +char-attr-invalid+)
177   (!set-constituent-trait #\Newline +char-attr-invalid+)
178   (dolist (c (list backspace-char-code tab-char-code form-feed-char-code
179                    return-char-code rubout-char-code))
180     (!set-constituent-trait (code-char c) +char-attr-invalid+)))
181
182 (defmacro get-constituent-trait (char)
183   `(if (typep ,char 'base-char)
184        (elt *constituent-trait-table* (char-code ,char))
185        +char-attr-constituent+))
186 \f
187 ;;;; readtable operations
188
189 (defun shallow-replace/eql-hash-table (to from)
190   (maphash (lambda (k v) (setf (gethash k to) v)) from))
191
192 (defun copy-readtable (&optional (from-readtable *readtable*)
193                                  to-readtable)
194   (let ((really-from-readtable (or from-readtable *standard-readtable*))
195         (really-to-readtable (or to-readtable (make-readtable))))
196     (replace (character-attribute-array really-to-readtable)
197              (character-attribute-array really-from-readtable))
198     (shallow-replace/eql-hash-table
199      (character-attribute-hash-table really-to-readtable)
200      (character-attribute-hash-table really-from-readtable))
201     (replace (character-macro-array really-to-readtable)
202              (character-macro-array really-from-readtable))
203     (shallow-replace/eql-hash-table
204      (character-macro-hash-table really-to-readtable)
205      (character-macro-hash-table really-from-readtable))
206     (setf (dispatch-tables really-to-readtable)
207           (mapcar (lambda (pair)
208                     (cons (car pair)
209                           (let ((table (make-hash-table)))
210                             (shallow-replace/eql-hash-table table (cdr pair))
211                             table)))
212                   (dispatch-tables really-from-readtable)))
213     (setf (readtable-case really-to-readtable)
214           (readtable-case really-from-readtable))
215     really-to-readtable))
216
217 (defun set-syntax-from-char (to-char from-char &optional
218                                      (to-readtable *readtable*)
219                                      (from-readtable ()))
220   #!+sb-doc
221   "Causes the syntax of TO-CHAR to be the same as FROM-CHAR in the
222   optional readtable (defaults to the current readtable). The
223   FROM-TABLE defaults to the standard Lisp readtable when NIL."
224   (let ((really-from-readtable (or from-readtable *standard-readtable*)))
225     (let ((att (get-cat-entry from-char really-from-readtable))
226           (mac (get-raw-cmt-entry from-char really-from-readtable))
227           (from-dpair (find from-char (dispatch-tables really-from-readtable)
228                             :test #'char= :key #'car))
229           (to-dpair (find to-char (dispatch-tables to-readtable)
230                           :test #'char= :key #'car)))
231       (set-cat-entry to-char att to-readtable)
232       (set-cmt-entry to-char mac to-readtable)
233       (when from-dpair
234         (cond
235           (to-dpair
236            (let ((table (cdr to-dpair)))
237              (clrhash table)
238              (shallow-replace/eql-hash-table table (cdr from-dpair))))
239           (t
240            (let ((pair (cons to-char (make-hash-table))))
241              (shallow-replace/eql-hash-table (cdr pair) (cdr from-dpair))
242              (setf (dispatch-tables to-readtable)
243                    (push pair (dispatch-tables to-readtable)))))))))
244   t)
245
246 (defun set-macro-character (char function &optional
247                                  (non-terminatingp nil)
248                                  (readtable *readtable*))
249   #!+sb-doc
250   "Causes CHAR to be a macro character which invokes FUNCTION when seen
251    by the reader. The NON-TERMINATINGP flag can be used to make the macro
252    character non-terminating, i.e. embeddable in a symbol name."
253   (let ((designated-readtable (or readtable *standard-readtable*)))
254     (set-cat-entry char (if non-terminatingp
255                             +char-attr-constituent+
256                             +char-attr-terminating-macro+)
257                    designated-readtable)
258     (set-cmt-entry char function designated-readtable)
259     t)) ; (ANSI-specified return value)
260
261 (defun get-macro-character (char &optional (readtable *readtable*))
262   #!+sb-doc
263   "Return the function associated with the specified CHAR which is a macro
264   character, or NIL if there is no such function. As a second value, return
265   T if CHAR is a macro character which is non-terminating, i.e. which can
266   be embedded in a symbol name."
267   (let* ((designated-readtable (or readtable *standard-readtable*))
268          ;; the first return value: a FUNCTION if CHAR is a macro
269          ;; character, or NIL otherwise
270          (fun-value (get-raw-cmt-entry char designated-readtable)))
271     (values fun-value
272             ;; NON-TERMINATING-P return value:
273             (if fun-value
274                 (or (constituentp char)
275                     (not (terminating-macrop char)))
276                 ;; ANSI's definition of GET-MACRO-CHARACTER says this
277                 ;; value is NIL when CHAR is not a macro character.
278                 ;; I.e. this value means not just "non-terminating
279                 ;; character?" but "non-terminating macro character?".
280                 nil))))
281 \f
282 ;;;; definitions to support internal programming conventions
283
284 (defmacro eofp (char)
285   `(eq ,char *eof-object*))
286
287 (defun flush-whitespace (stream)
288   ;; This flushes whitespace chars, returning the last char it read (a
289   ;; non-white one). It always gets an error on end-of-file.
290   (let ((stream (in-synonym-of stream)))
291     (if (ansi-stream-p stream)
292         (prepare-for-fast-read-char stream
293           (do ((attribute-array (character-attribute-array *readtable*))
294                (attribute-hash-table
295                 (character-attribute-hash-table *readtable*))
296                (char (fast-read-char t) (fast-read-char t)))
297               ((/= (the fixnum
298                      (if (typep char 'base-char)
299                          (aref attribute-array (char-code char))
300                          (gethash char attribute-hash-table
301                                   +char-attr-constituent+)))
302                    +char-attr-whitespace+)
303                (done-with-fast-read-char)
304                char)))
305         ;; CLOS stream
306         (do ((attribute-array (character-attribute-array *readtable*))
307              (attribute-hash-table
308               (character-attribute-hash-table *readtable*))
309              (char (read-char stream nil :eof) (read-char stream nil :eof)))
310             ((or (eq char :eof)
311                  (/= (the fixnum
312                        (if (typep char 'base-char)
313                            (aref attribute-array (char-code char))
314                            (gethash char attribute-hash-table
315                                     +char-attr-constituent+)))
316                      +char-attr-whitespace+))
317              (if (eq char :eof)
318                  (error 'end-of-file :stream stream)
319                  char))))))
320 \f
321 ;;;; temporary initialization hack
322
323 (defun !cold-init-standard-readtable ()
324   (setq *standard-readtable* (make-readtable))
325   ;; All characters get boring defaults in MAKE-READTABLE. Now we
326   ;; override the boring defaults on characters which need more
327   ;; interesting behavior.
328   (let ((*readtable* *standard-readtable*))
329
330     (flet ((whitespaceify (char)
331              (set-cmt-entry char nil)
332              (set-cat-entry char +char-attr-whitespace+)))
333       (whitespaceify (code-char tab-char-code))
334       (whitespaceify #\Newline)
335       (whitespaceify #\Space)
336       (whitespaceify (code-char form-feed-char-code))
337       (whitespaceify (code-char return-char-code)))
338
339     (set-cat-entry #\\ +char-attr-single-escape+)
340     (set-cmt-entry #\\ nil)
341
342     (set-cat-entry #\| +char-attr-multiple-escape+)
343     (set-cmt-entry #\| nil)
344
345     ;; Easy macro-character definitions are in this source file.
346     (set-macro-character #\" #'read-string)
347     (set-macro-character #\' #'read-quote)
348     (set-macro-character #\( #'read-list)
349     (set-macro-character #\) #'read-right-paren)
350     (set-macro-character #\; #'read-comment)
351     ;; (The hairier macro-character definitions, for #\# and #\`, are
352     ;; defined elsewhere, in their own source files.)
353
354     ;; all constituents
355     (do ((ichar 0 (1+ ichar))
356          (char))
357         ((= ichar base-char-code-limit))
358       (setq char (code-char ichar))
359       (when (constituentp char *standard-readtable*)
360         (set-cmt-entry char nil)))))
361 \f
362 ;;;; implementation of the read buffer
363
364 (defvar *read-buffer*)
365 (defvar *read-buffer-length*)
366 ;;; FIXME: Is it really helpful to have *READ-BUFFER-LENGTH* be a
367 ;;; separate variable instead of just calculating it on the fly as
368 ;;; (LENGTH *READ-BUFFER*)?
369
370 (defvar *inch-ptr*)
371 (defvar *ouch-ptr*)
372
373 (declaim (type index *read-buffer-length* *inch-ptr* *ouch-ptr*))
374 (declaim (type (simple-array character (*)) *read-buffer*))
375
376 (defmacro reset-read-buffer ()
377   ;; Turn *READ-BUFFER* into an empty read buffer.
378   `(progn
379      ;; *OUCH-PTR* always points to next char to write.
380      (setq *ouch-ptr* 0)
381      ;; *INCH-PTR* always points to next char to read.
382      (setq *inch-ptr* 0)))
383
384 ;;; FIXME I removed "THE FIXNUM"'s from OUCH-READ-BUFFER and
385 ;;; OUCH-UNREAD-BUFFER, check to make sure that Python really is smart
386 ;;; enough to make good code without them. And while I'm at it,
387 ;;; converting them from macros to inline functions might be good,
388 ;;; too.
389
390 (defmacro ouch-read-buffer (char)
391   `(progn
392      ;; When buffer overflow
393      (when (>= *ouch-ptr* *read-buffer-length*)
394        ;; Size should be doubled.
395        (grow-read-buffer))
396      (setf (elt (the simple-string *read-buffer*) *ouch-ptr*) ,char)
397      (setq *ouch-ptr* (1+ *ouch-ptr*))))
398
399 ;;; macro to move *ouch-ptr* back one.
400 (defmacro ouch-unread-buffer ()
401   '(when (> *ouch-ptr* *inch-ptr*)
402      (setq *ouch-ptr* (1- (the fixnum *ouch-ptr*)))))
403
404 (defun grow-read-buffer ()
405   (let ((rbl (length (the simple-string *read-buffer*))))
406     (setq *read-buffer*
407           (concatenate 'simple-string
408                        *read-buffer*
409                        (make-string rbl)))
410     (setq *read-buffer-length* (* 2 rbl))))
411
412 (defun inchpeek-read-buffer ()
413   (if (>= (the fixnum *inch-ptr*) (the fixnum *ouch-ptr*))
414       *eof-object*
415       (elt *read-buffer* *inch-ptr*)))
416
417 (defun inch-read-buffer ()
418   (if (>= *inch-ptr* *ouch-ptr*)
419       *eof-object*
420       (prog1
421           (elt *read-buffer* *inch-ptr*)
422         (incf *inch-ptr*))))
423
424 (defmacro unread-buffer ()
425   `(decf *inch-ptr*))
426
427 (defun read-unwind-read-buffer ()
428   ;; Keep contents, but make next (INCH..) return first character.
429   (setq *inch-ptr* 0))
430
431 (defun read-buffer-to-string ()
432   (subseq *read-buffer* 0 *ouch-ptr*))
433
434 (defmacro with-reader ((&optional recursive-p) &body body)
435   #!+sb-doc
436   "If RECURSIVE-P is NIL, bind *READER-BUFFER* and its subservient
437 variables to allow for nested and thread safe reading."
438   `(if ,recursive-p
439        (progn ,@body)
440        (let* ((*read-buffer* (make-string 128))
441               (*read-buffer-length* 128)
442               (*ouch-ptr* 0)
443               (*inch-ptr* 0))
444          ,@body)))
445 \f
446 ;;;; READ-PRESERVING-WHITESPACE, READ-DELIMITED-LIST, and READ
447
448 ;;; an alist for #=, used to keep track of objects with labels assigned that
449 ;;; have been completely read. Each entry is (integer-tag gensym-tag value).
450 ;;;
451 ;;; KLUDGE: Should this really be an alist? It seems as though users
452 ;;; could reasonably expect N log N performance for large datasets.
453 ;;; On the other hand, it's probably very very seldom a problem in practice.
454 ;;; On the third hand, it might be just as easy to use a hash table
455 ;;; as an alist, so maybe we should. -- WHN 19991202
456 (defvar *sharp-equal-alist* ())
457
458 (declaim (special *standard-input*))
459
460 ;;; READ-PRESERVING-WHITESPACE behaves just like READ, only it makes
461 ;;; sure to leave terminating whitespace in the stream. (This is a
462 ;;; COMMON-LISP exported symbol.)
463 (defun read-preserving-whitespace (&optional (stream *standard-input*)
464                                              (eof-error-p t)
465                                              (eof-value nil)
466                                              (recursivep nil))
467   #!+sb-doc
468   "Read from STREAM and return the value read, preserving any whitespace
469    that followed the object."
470   (if recursivep
471       ;; a loop for repeating when a macro returns nothing
472       (loop
473        (let ((char (read-char stream eof-error-p *eof-object*)))
474          (cond ((eofp char) (return eof-value))
475                ((whitespace[2]p char))
476                (t
477                 (let* ((macrofun (get-coerced-cmt-entry char *readtable*))
478                        (result (multiple-value-list
479                                 (funcall macrofun stream char))))
480                   ;; Repeat if macro returned nothing.
481                   (when result
482                     (return (unless *read-suppress* (car result)))))))))
483       (with-reader ()
484         (let ((*sharp-equal-alist* nil))
485           (read-preserving-whitespace stream eof-error-p eof-value t)))))
486
487 ;;; Return NIL or a list with one thing, depending.
488 ;;;
489 ;;; for functions that want comments to return so that they can look
490 ;;; past them. We assume CHAR is not whitespace.
491 (defun read-maybe-nothing (stream char)
492   (let ((retval (multiple-value-list
493                  (funcall (get-coerced-cmt-entry char *readtable*)
494                           stream
495                           char))))
496     (if retval (rplacd retval nil))))
497
498 (defun read (&optional (stream *standard-input*)
499                        (eof-error-p t)
500                        (eof-value ())
501                        (recursivep ()))
502   #!+sb-doc
503   "Read the next Lisp value from STREAM, and return it."
504   (let ((result (read-preserving-whitespace stream
505                                             eof-error-p
506                                             eof-value
507                                             recursivep)))
508     ;; This function generally discards trailing whitespace. If you
509     ;; don't want to discard trailing whitespace, call
510     ;; CL:READ-PRESERVING-WHITESPACE instead.
511     (unless (or (eql result eof-value) recursivep)
512       (let ((next-char (read-char stream nil nil)))
513         (unless (or (null next-char)
514                     (whitespace[2]p next-char))
515           (unread-char next-char stream))))
516     result))
517
518 ;;; (This is a COMMON-LISP exported symbol.)
519 (defun read-delimited-list (endchar &optional
520                                     (input-stream *standard-input*)
521                                     recursive-p)
522   #!+sb-doc
523   "Read Lisp values from INPUT-STREAM until the next character after a
524    value's representation is ENDCHAR, and return the objects as a list."
525   (with-reader (recursive-p)
526     (do ((char (flush-whitespace input-stream)
527                (flush-whitespace input-stream))
528          (retlist ()))
529         ((char= char endchar) (unless *read-suppress* (nreverse retlist)))
530       (setq retlist (nconc (read-maybe-nothing input-stream char) retlist)))))
531 \f
532 ;;;; basic readmacro definitions
533 ;;;;
534 ;;;; Some large, hairy subsets of readmacro definitions (backquotes
535 ;;;; and sharp macros) are not here, but in their own source files.
536
537 (defun read-quote (stream ignore)
538   (declare (ignore ignore))
539   (list 'quote (read stream t nil t)))
540
541 (defun read-comment (stream ignore)
542   (declare (ignore ignore))
543   (handler-bind
544       ((character-decoding-error
545         #'(lambda (decoding-error)
546             (declare (ignorable decoding-error))
547             (style-warn "Character decoding error in a ;-comment at position ~A reading source file ~A, resyncing." (file-position stream) stream)
548             (invoke-restart 'attempt-resync))))
549     (let ((stream (in-synonym-of stream)))
550       (if (ansi-stream-p stream)
551           (prepare-for-fast-read-char stream
552            (do ((char (fast-read-char nil nil)
553                       (fast-read-char nil nil)))
554                ((or (not char) (char= char #\newline))
555                 (done-with-fast-read-char))))
556           ;; CLOS stream
557           (do ((char (read-char stream nil :eof) (read-char stream nil :eof)))
558               ((or (eq char :eof) (char= char #\newline)))))))
559   ;; Don't return anything.
560   (values))
561
562 (defun read-list (stream ignore)
563   (declare (ignore ignore))
564   (let* ((thelist (list nil))
565          (listtail thelist))
566     (do ((firstchar (flush-whitespace stream) (flush-whitespace stream)))
567         ((char= firstchar #\) ) (cdr thelist))
568       (when (char= firstchar #\.)
569             (let ((nextchar (read-char stream t)))
570               (cond ((token-delimiterp nextchar)
571                      (cond ((eq listtail thelist)
572                             (unless *read-suppress*
573                               (%reader-error
574                                stream
575                                "Nothing appears before . in list.")))
576                            ((whitespace[2]p nextchar)
577                             (setq nextchar (flush-whitespace stream))))
578                      (rplacd listtail
579                              ;; Return list containing last thing.
580                              (car (read-after-dot stream nextchar)))
581                      (return (cdr thelist)))
582                     ;; Put back NEXTCHAR so that we can read it normally.
583                     (t (unread-char nextchar stream)))))
584       ;; Next thing is not an isolated dot.
585       (let ((listobj (read-maybe-nothing stream firstchar)))
586         ;; allows the possibility that a comment was read
587         (when listobj
588               (rplacd listtail listobj)
589               (setq listtail listobj))))))
590
591 (defun read-after-dot (stream firstchar)
592   ;; FIRSTCHAR is non-whitespace!
593   (let ((lastobj ()))
594     (do ((char firstchar (flush-whitespace stream)))
595         ((char= char #\) )
596          (if *read-suppress*
597              (return-from read-after-dot nil)
598              (%reader-error stream "Nothing appears after . in list.")))
599       ;; See whether there's something there.
600       (setq lastobj (read-maybe-nothing stream char))
601       (when lastobj (return t)))
602     ;; At least one thing appears after the dot.
603     ;; Check for more than one thing following dot.
604     (do ((lastchar (flush-whitespace stream)
605                    (flush-whitespace stream)))
606         ((char= lastchar #\) ) lastobj) ;success!
607       ;; Try reading virtual whitespace.
608       (if (and (read-maybe-nothing stream lastchar)
609                (not *read-suppress*))
610           (%reader-error stream "More than one object follows . in list.")))))
611
612 (defun read-string (stream closech)
613   ;; This accumulates chars until it sees same char that invoked it.
614   ;; For a very long string, this could end up bloating the read buffer.
615   (reset-read-buffer)
616   (let ((stream (in-synonym-of stream)))
617     (if (ansi-stream-p stream)
618         (prepare-for-fast-read-char stream
619           (do ((char (fast-read-char t) (fast-read-char t)))
620               ((char= char closech)
621                (done-with-fast-read-char))
622             (if (single-escape-p char) (setq char (fast-read-char t)))
623             (ouch-read-buffer char)))
624         ;; CLOS stream
625         (do ((char (read-char stream nil :eof) (read-char stream nil :eof)))
626             ((or (eq char :eof) (char= char closech))
627              (if (eq char :eof)
628                  (error 'end-of-file :stream stream)))
629           (when (single-escape-p char)
630             (setq char (read-char stream nil :eof))
631             (if (eq char :eof)
632                 (error 'end-of-file :stream stream)))
633           (ouch-read-buffer char))))
634   (read-buffer-to-string))
635
636 (defun read-right-paren (stream ignore)
637   (declare (ignore ignore))
638   (%reader-error stream "unmatched close parenthesis"))
639
640 ;;; Read from the stream up to the next delimiter. Leave the resulting
641 ;;; token in *READ-BUFFER*, and return two values:
642 ;;; -- a list of the escaped character positions, and
643 ;;; -- The position of the first package delimiter (or NIL).
644 (defun internal-read-extended-token (stream firstchar escape-firstchar)
645   (reset-read-buffer)
646   (let ((escapes '()))
647     (when escape-firstchar
648       (push *ouch-ptr* escapes)
649       (ouch-read-buffer firstchar)
650       (setq firstchar (read-char stream nil *eof-object*)))
651   (do ((char firstchar (read-char stream nil *eof-object*))
652        (colon nil))
653       ((cond ((eofp char) t)
654              ((token-delimiterp char)
655               (unread-char char stream)
656               t)
657              (t nil))
658        (values escapes colon))
659     (cond ((single-escape-p char)
660            ;; It can't be a number, even if it's 1\23.
661            ;; Read next char here, so it won't be casified.
662            (push *ouch-ptr* escapes)
663            (let ((nextchar (read-char stream nil *eof-object*)))
664              (if (eofp nextchar)
665                  (reader-eof-error stream "after escape character")
666                  (ouch-read-buffer nextchar))))
667           ((multiple-escape-p char)
668            ;; Read to next multiple-escape, escaping single chars
669            ;; along the way.
670            (loop
671              (let ((ch (read-char stream nil *eof-object*)))
672                (cond
673                 ((eofp ch)
674                  (reader-eof-error stream "inside extended token"))
675                 ((multiple-escape-p ch) (return))
676                 ((single-escape-p ch)
677                  (let ((nextchar (read-char stream nil *eof-object*)))
678                    (cond ((eofp nextchar)
679                           (reader-eof-error stream "after escape character"))
680                          (t
681                           (push *ouch-ptr* escapes)
682                           (ouch-read-buffer nextchar)))))
683                 (t
684                  (push *ouch-ptr* escapes)
685                  (ouch-read-buffer ch))))))
686           (t
687            (when (and (constituentp char)
688                       (eql (get-constituent-trait char)
689                            +char-attr-package-delimiter+)
690                       (not colon))
691              (setq colon *ouch-ptr*))
692            (ouch-read-buffer char))))))
693 \f
694 ;;;; character classes
695
696 ;;; Return the character class for CHAR.
697 ;;;
698 ;;; FIXME: why aren't these ATT-getting forms using GET-CAT-ENTRY?
699 ;;; Because we've cached the readtable tables?
700 (defmacro char-class (char attarray atthash)
701   `(let ((att (if (typep ,char 'base-char)
702                   (aref ,attarray (char-code ,char))
703                   (gethash ,char ,atthash +char-attr-constituent+))))
704      (declare (fixnum att))
705      (cond
706        ((<= att +char-attr-terminating-macro+) +char-attr-delimiter+)
707        ((< att +char-attr-constituent+) att)
708        (t (setf att (get-constituent-trait ,char))
709           (if (= att +char-attr-invalid+)
710               (%reader-error stream "invalid constituent")
711               att)))))
712
713 ;;; Return the character class for CHAR, which might be part of a
714 ;;; rational number.
715 (defmacro char-class2 (char attarray atthash)
716   `(let ((att (if (typep ,char 'base-char)
717                   (aref ,attarray (char-code ,char))
718                   (gethash ,char ,atthash +char-attr-constituent+))))
719      (declare (fixnum att))
720      (cond
721        ((<= att +char-attr-terminating-macro+) +char-attr-delimiter+)
722        ((< att +char-attr-constituent+) att)
723        (t (setf att (get-constituent-trait ,char))
724           (cond
725             ((digit-char-p ,char *read-base*) +char-attr-constituent-digit+)
726             ((= att +char-attr-constituent-digit+) +char-attr-constituent+)
727             ((= att +char-attr-invalid+)
728              (%reader-error stream "invalid constituent"))
729             (t att))))))
730
731 ;;; Return the character class for a char which might be part of a
732 ;;; rational or floating number. (Assume that it is a digit if it
733 ;;; could be.)
734 (defmacro char-class3 (char attarray atthash)
735   `(let ((att (if (typep ,char 'base-char)
736                   (aref ,attarray (char-code ,char))
737                   (gethash ,char ,atthash +char-attr-constituent+))))
738      (declare (fixnum att))
739      (cond
740        ((<= att +char-attr-terminating-macro+) +char-attr-delimiter+)
741        ((< att +char-attr-constituent+) att)
742        (t (setf att (get-constituent-trait ,char))
743           (when possibly-rational
744             (setq possibly-rational
745                   (or (digit-char-p ,char *read-base*)
746                       (= att +char-attr-constituent-slash+))))
747           (when possibly-float
748             (setq possibly-float
749                   (or (digit-char-p ,char 10)
750                       (= att +char-attr-constituent-dot+))))
751           (cond
752             ((digit-char-p ,char (max *read-base* 10))
753              (if (digit-char-p ,char *read-base*)
754                  (if (= att +char-attr-constituent-expt+)
755                      +char-attr-constituent-digit-or-expt+
756                      +char-attr-constituent-digit+)
757                  +char-attr-constituent-decimal-digit+))
758             ((= att +char-attr-invalid+)
759              (%reader-error stream "invalid constituent"))
760             (t att))))))
761 \f
762 ;;;; token fetching
763
764 (defvar *read-suppress* nil
765   #!+sb-doc
766   "Suppress most interpreting in the reader when T.")
767
768 (defvar *read-base* 10
769   #!+sb-doc
770   "the radix that Lisp reads numbers in")
771 (declaim (type (integer 2 36) *read-base*))
772
773 ;;; Modify the read buffer according to READTABLE-CASE, ignoring
774 ;;; ESCAPES. ESCAPES is a list of the escaped indices, in reverse
775 ;;; order.
776 (defun casify-read-buffer (escapes)
777   (let ((case (readtable-case *readtable*)))
778     (cond
779      ((and (null escapes) (eq case :upcase))
780       (dotimes (i *ouch-ptr*)
781         (setf (schar *read-buffer* i)
782               (char-upcase (schar *read-buffer* i)))))
783      ((eq case :preserve))
784      (t
785       (macrolet ((skip-esc (&body body)
786                    `(do ((i (1- *ouch-ptr*) (1- i))
787                          (escapes escapes))
788                         ((minusp i))
789                       (declare (fixnum i))
790                       (when (or (null escapes)
791                                 (let ((esc (first escapes)))
792                                   (declare (fixnum esc))
793                                   (cond ((< esc i) t)
794                                         (t
795                                          (aver (= esc i))
796                                          (pop escapes)
797                                          nil))))
798                         (let ((ch (schar *read-buffer* i)))
799                           ,@body)))))
800         (flet ((lower-em ()
801                  (skip-esc (setf (schar *read-buffer* i) (char-downcase ch))))
802                (raise-em ()
803                  (skip-esc (setf (schar *read-buffer* i) (char-upcase ch)))))
804           (ecase case
805             (:upcase (raise-em))
806             (:downcase (lower-em))
807             (:invert
808              (let ((all-upper t)
809                    (all-lower t))
810                (skip-esc
811                  (when (both-case-p ch)
812                    (if (upper-case-p ch)
813                        (setq all-lower nil)
814                        (setq all-upper nil))))
815                (cond (all-lower (raise-em))
816                      (all-upper (lower-em))))))))))))
817
818 (defun read-token (stream firstchar)
819   #!+sb-doc
820   "This function is just an fsm that recognizes numbers and symbols."
821   ;; Check explicitly whether FIRSTCHAR has an entry for
822   ;; NON-TERMINATING in CHARACTER-ATTRIBUTE-TABLE and
823   ;; READ-DOT-NUMBER-SYMBOL in CMT. Report an error if these are
824   ;; violated. (If we called this, we want something that is a
825   ;; legitimate token!) Read in the longest possible string satisfying
826   ;; the Backus-Naur form for "unqualified-token". Leave the result in
827   ;; the *READ-BUFFER*. Return next char after token (last char read).
828   (when *read-suppress*
829     (internal-read-extended-token stream firstchar nil)
830     (return-from read-token nil))
831   (let ((attribute-array (character-attribute-array *readtable*))
832         (attribute-hash-table (character-attribute-hash-table *readtable*))
833         (package-designator nil)
834         (colons 0)
835         (possibly-rational t)
836         (seen-digit-or-expt nil)
837         (possibly-float t)
838         (was-possibly-float nil)
839         (escapes ())
840         (seen-multiple-escapes nil))
841     (reset-read-buffer)
842     (prog ((char firstchar))
843       (case (char-class3 char attribute-array attribute-hash-table)
844         (#.+char-attr-constituent-sign+ (go SIGN))
845         (#.+char-attr-constituent-digit+ (go LEFTDIGIT))
846         (#.+char-attr-constituent-digit-or-expt+
847          (setq seen-digit-or-expt t)
848          (go LEFTDIGIT))
849         (#.+char-attr-constituent-decimal-digit+ (go LEFTDECIMALDIGIT))
850         (#.+char-attr-constituent-dot+ (go FRONTDOT))
851         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
852         (#.+char-attr-package-delimiter+ (go COLON))
853         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
854         (#.+char-attr-invalid+ (%reader-error stream "invalid constituent"))
855         ;; can't have eof, whitespace, or terminating macro as first char!
856         (t (go SYMBOL)))
857      SIGN ; saw "sign"
858       (ouch-read-buffer char)
859       (setq char (read-char stream nil nil))
860       (unless char (go RETURN-SYMBOL))
861       (setq possibly-rational t
862             possibly-float t)
863       (case (char-class3 char attribute-array attribute-hash-table)
864         (#.+char-attr-constituent-digit+ (go LEFTDIGIT))
865         (#.+char-attr-constituent-digit-or-expt+
866          (setq seen-digit-or-expt t)
867          (go LEFTDIGIT))
868         (#.+char-attr-constituent-decimal-digit+ (go LEFTDECIMALDIGIT))
869         (#.+char-attr-constituent-dot+ (go SIGNDOT))
870         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
871         (#.+char-attr-package-delimiter+ (go COLON))
872         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
873         (#.+char-attr-delimiter+ (unread-char char stream) (go RETURN-SYMBOL))
874         (t (go SYMBOL)))
875      LEFTDIGIT ; saw "[sign] {digit}+"
876       (ouch-read-buffer char)
877       (setq char (read-char stream nil nil))
878       (unless char (return (make-integer)))
879       (setq was-possibly-float possibly-float)
880       (case (char-class3 char attribute-array attribute-hash-table)
881         (#.+char-attr-constituent-digit+ (go LEFTDIGIT))
882         (#.+char-attr-constituent-decimal-digit+ (if possibly-float
883                                                      (go LEFTDECIMALDIGIT)
884                                                      (go SYMBOL)))
885         (#.+char-attr-constituent-dot+ (if possibly-float
886                                            (go MIDDLEDOT)
887                                            (go SYMBOL)))
888         (#.+char-attr-constituent-digit-or-expt+
889          (if (or seen-digit-or-expt (not was-possibly-float))
890              (progn (setq seen-digit-or-expt t) (go LEFTDIGIT))
891              (progn (setq seen-digit-or-expt t) (go LEFTDIGIT-OR-EXPT))))
892         (#.+char-attr-constituent-expt+
893          (if was-possibly-float
894              (go EXPONENT)
895              (go SYMBOL)))
896         (#.+char-attr-constituent-slash+ (if possibly-rational
897                                              (go RATIO)
898                                              (go SYMBOL)))
899         (#.+char-attr-delimiter+ (unread-char char stream)
900                                  (return (make-integer)))
901         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
902         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
903         (#.+char-attr-package-delimiter+ (go COLON))
904         (t (go SYMBOL)))
905      LEFTDIGIT-OR-EXPT
906       (ouch-read-buffer char)
907       (setq char (read-char stream nil nil))
908       (unless char (return (make-integer)))
909       (case (char-class3 char attribute-array attribute-hash-table)
910         (#.+char-attr-constituent-digit+ (go LEFTDIGIT))
911         (#.+char-attr-constituent-decimal-digit+ (bug "impossible!"))
912         (#.+char-attr-constituent-dot+ (go SYMBOL))
913         (#.+char-attr-constituent-digit-or-expt+ (go LEFTDIGIT))
914         (#.+char-attr-constituent-expt+ (go SYMBOL))
915         (#.+char-attr-constituent-sign+ (go EXPTSIGN))
916         (#.+char-attr-constituent-slash+ (if possibly-rational
917                                              (go RATIO)
918                                              (go SYMBOL)))
919         (#.+char-attr-delimiter+ (unread-char char stream)
920                                  (return (make-integer)))
921         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
922         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
923         (#.+char-attr-package-delimiter+ (go COLON))
924         (t (go SYMBOL)))
925      LEFTDECIMALDIGIT ; saw "[sign] {decimal-digit}+"
926       (aver possibly-float)
927       (ouch-read-buffer char)
928       (setq char (read-char stream nil nil))
929       (unless char (go RETURN-SYMBOL))
930       (case (char-class char attribute-array attribute-hash-table)
931         (#.+char-attr-constituent-digit+ (go LEFTDECIMALDIGIT))
932         (#.+char-attr-constituent-dot+ (go MIDDLEDOT))
933         (#.+char-attr-constituent-expt+ (go EXPONENT))
934         (#.+char-attr-constituent-slash+ (aver (not possibly-rational))
935                                          (go SYMBOL))
936         (#.+char-attr-delimiter+ (unread-char char stream)
937                                  (go RETURN-SYMBOL))
938         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
939         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
940         (#.+char-attr-package-delimiter+ (go COLON))
941         (t (go SYMBOL)))
942      MIDDLEDOT ; saw "[sign] {digit}+ dot"
943       (ouch-read-buffer char)
944       (setq char (read-char stream nil nil))
945       (unless char (return (let ((*read-base* 10))
946                              (make-integer))))
947       (case (char-class char attribute-array attribute-hash-table)
948         (#.+char-attr-constituent-digit+ (go RIGHTDIGIT))
949         (#.+char-attr-constituent-expt+ (go EXPONENT))
950         (#.+char-attr-delimiter+
951          (unread-char char stream)
952          (return (let ((*read-base* 10))
953                    (make-integer))))
954         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
955         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
956         (#.+char-attr-package-delimiter+ (go COLON))
957         (t (go SYMBOL)))
958      RIGHTDIGIT ; saw "[sign] {decimal-digit}* dot {digit}+"
959       (ouch-read-buffer char)
960       (setq char (read-char stream nil nil))
961       (unless char (return (make-float stream)))
962       (case (char-class char attribute-array attribute-hash-table)
963         (#.+char-attr-constituent-digit+ (go RIGHTDIGIT))
964         (#.+char-attr-constituent-expt+ (go EXPONENT))
965         (#.+char-attr-delimiter+
966          (unread-char char stream)
967          (return (make-float stream)))
968         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
969         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
970         (#.+char-attr-package-delimiter+ (go COLON))
971         (t (go SYMBOL)))
972      SIGNDOT ; saw "[sign] dot"
973       (ouch-read-buffer char)
974       (setq char (read-char stream nil nil))
975       (unless char (go RETURN-SYMBOL))
976       (case (char-class char attribute-array attribute-hash-table)
977         (#.+char-attr-constituent-digit+ (go RIGHTDIGIT))
978         (#.+char-attr-delimiter+ (unread-char char stream) (go RETURN-SYMBOL))
979         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
980         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
981         (t (go SYMBOL)))
982      FRONTDOT ; saw "dot"
983       (ouch-read-buffer char)
984       (setq char (read-char stream nil nil))
985       (unless char (%reader-error stream "dot context error"))
986       (case (char-class char attribute-array attribute-hash-table)
987         (#.+char-attr-constituent-digit+ (go RIGHTDIGIT))
988         (#.+char-attr-constituent-dot+ (go DOTS))
989         (#.+char-attr-delimiter+  (%reader-error stream "dot context error"))
990         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
991         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
992         (#.+char-attr-package-delimiter+ (go COLON))
993         (t (go SYMBOL)))
994      EXPONENT
995       (ouch-read-buffer char)
996       (setq char (read-char stream nil nil))
997       (unless char (go RETURN-SYMBOL))
998       (setq possibly-float t)
999       (case (char-class char attribute-array attribute-hash-table)
1000         (#.+char-attr-constituent-sign+ (go EXPTSIGN))
1001         (#.+char-attr-constituent-digit+ (go EXPTDIGIT))
1002         (#.+char-attr-delimiter+ (unread-char char stream) (go RETURN-SYMBOL))
1003         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1004         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1005         (#.+char-attr-package-delimiter+ (go COLON))
1006         (t (go SYMBOL)))
1007      EXPTSIGN ; got to EXPONENT, and saw a sign character
1008       (ouch-read-buffer char)
1009       (setq char (read-char stream nil nil))
1010       (unless char (go RETURN-SYMBOL))
1011       (case (char-class char attribute-array attribute-hash-table)
1012         (#.+char-attr-constituent-digit+ (go EXPTDIGIT))
1013         (#.+char-attr-delimiter+ (unread-char char stream) (go RETURN-SYMBOL))
1014         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1015         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1016         (#.+char-attr-package-delimiter+ (go COLON))
1017         (t (go SYMBOL)))
1018      EXPTDIGIT ; got to EXPONENT, saw "[sign] {digit}+"
1019       (ouch-read-buffer char)
1020       (setq char (read-char stream nil nil))
1021       (unless char (return (make-float stream)))
1022       (case (char-class char attribute-array attribute-hash-table)
1023         (#.+char-attr-constituent-digit+ (go EXPTDIGIT))
1024         (#.+char-attr-delimiter+
1025          (unread-char char stream)
1026          (return (make-float stream)))
1027         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1028         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1029         (#.+char-attr-package-delimiter+ (go COLON))
1030         (t (go SYMBOL)))
1031      RATIO ; saw "[sign] {digit}+ slash"
1032       (ouch-read-buffer char)
1033       (setq char (read-char stream nil nil))
1034       (unless char (go RETURN-SYMBOL))
1035       (case (char-class2 char attribute-array attribute-hash-table)
1036         (#.+char-attr-constituent-digit+ (go RATIODIGIT))
1037         (#.+char-attr-delimiter+ (unread-char char stream) (go RETURN-SYMBOL))
1038         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1039         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1040         (#.+char-attr-package-delimiter+ (go COLON))
1041         (t (go SYMBOL)))
1042      RATIODIGIT ; saw "[sign] {digit}+ slash {digit}+"
1043       (ouch-read-buffer char)
1044       (setq char (read-char stream nil nil))
1045       (unless char (return (make-ratio stream)))
1046       (case (char-class2 char attribute-array attribute-hash-table)
1047         (#.+char-attr-constituent-digit+ (go RATIODIGIT))
1048         (#.+char-attr-delimiter+
1049          (unread-char char stream)
1050          (return (make-ratio stream)))
1051         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1052         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1053         (#.+char-attr-package-delimiter+ (go COLON))
1054         (t (go SYMBOL)))
1055      DOTS ; saw "dot {dot}+"
1056       (ouch-read-buffer char)
1057       (setq char (read-char stream nil nil))
1058       (unless char (%reader-error stream "too many dots"))
1059       (case (char-class char attribute-array attribute-hash-table)
1060         (#.+char-attr-constituent-dot+ (go DOTS))
1061         (#.+char-attr-delimiter+
1062          (unread-char char stream)
1063          (%reader-error stream "too many dots"))
1064         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1065         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1066         (#.+char-attr-package-delimiter+ (go COLON))
1067         (t (go SYMBOL)))
1068      SYMBOL ; not a dot, dots, or number
1069       (let ((stream (in-synonym-of stream)))
1070         (if (ansi-stream-p stream)
1071             (prepare-for-fast-read-char stream
1072               (prog ()
1073                SYMBOL-LOOP
1074                (ouch-read-buffer char)
1075                (setq char (fast-read-char nil nil))
1076                (unless char (go RETURN-SYMBOL))
1077                (case (char-class char attribute-array attribute-hash-table)
1078                  (#.+char-attr-single-escape+ (done-with-fast-read-char)
1079                                               (go SINGLE-ESCAPE))
1080                  (#.+char-attr-delimiter+ (done-with-fast-read-char)
1081                                           (unread-char char stream)
1082                                           (go RETURN-SYMBOL))
1083                  (#.+char-attr-multiple-escape+ (done-with-fast-read-char)
1084                                                 (go MULT-ESCAPE))
1085                  (#.+char-attr-package-delimiter+ (done-with-fast-read-char)
1086                                                   (go COLON))
1087                  (t (go SYMBOL-LOOP)))))
1088             ;; CLOS stream
1089             (prog ()
1090              SYMBOL-LOOP
1091              (ouch-read-buffer char)
1092              (setq char (read-char stream nil :eof))
1093              (when (eq char :eof) (go RETURN-SYMBOL))
1094              (case (char-class char attribute-array attribute-hash-table)
1095                (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1096                (#.+char-attr-delimiter+ (unread-char char stream)
1097                             (go RETURN-SYMBOL))
1098                (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1099                (#.+char-attr-package-delimiter+ (go COLON))
1100                (t (go SYMBOL-LOOP))))))
1101      SINGLE-ESCAPE ; saw a single-escape
1102       ;; Don't put the escape character in the read buffer.
1103       ;; READ-NEXT CHAR, put in buffer (no case conversion).
1104       (let ((nextchar (read-char stream nil nil)))
1105         (unless nextchar
1106           (reader-eof-error stream "after single-escape character"))
1107         (push *ouch-ptr* escapes)
1108         (ouch-read-buffer nextchar))
1109       (setq char (read-char stream nil nil))
1110       (unless char (go RETURN-SYMBOL))
1111       (case (char-class char attribute-array attribute-hash-table)
1112         (#.+char-attr-delimiter+ (unread-char char stream) (go RETURN-SYMBOL))
1113         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1114         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1115         (#.+char-attr-package-delimiter+ (go COLON))
1116         (t (go SYMBOL)))
1117       MULT-ESCAPE
1118       (setq seen-multiple-escapes t)
1119       (do ((char (read-char stream t) (read-char stream t)))
1120           ((multiple-escape-p char))
1121         (if (single-escape-p char) (setq char (read-char stream t)))
1122         (push *ouch-ptr* escapes)
1123         (ouch-read-buffer char))
1124       (setq char (read-char stream nil nil))
1125       (unless char (go RETURN-SYMBOL))
1126       (case (char-class char attribute-array attribute-hash-table)
1127         (#.+char-attr-delimiter+ (unread-char char stream) (go RETURN-SYMBOL))
1128         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1129         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1130         (#.+char-attr-package-delimiter+ (go COLON))
1131         (t (go SYMBOL)))
1132       COLON
1133       (casify-read-buffer escapes)
1134       (unless (zerop colons)
1135         (%reader-error stream "too many colons in ~S"
1136                       (read-buffer-to-string)))
1137       (setq colons 1)
1138       (setq package-designator
1139             (if (plusp *ouch-ptr*)
1140                 ;; FIXME: It seems inefficient to cons up a package
1141                 ;; designator string every time we read a symbol with an
1142                 ;; explicit package prefix. Perhaps we could implement
1143                 ;; a FIND-PACKAGE* function analogous to INTERN*
1144                 ;; and friends?
1145                 (read-buffer-to-string)
1146                 (if seen-multiple-escapes
1147                     (read-buffer-to-string)
1148                     *keyword-package*)))
1149       (reset-read-buffer)
1150       (setq escapes ())
1151       (setq char (read-char stream nil nil))
1152       (unless char (reader-eof-error stream "after reading a colon"))
1153       (case (char-class char attribute-array attribute-hash-table)
1154         (#.+char-attr-delimiter+
1155          (unread-char char stream)
1156          (%reader-error stream
1157                         "illegal terminating character after a colon: ~S"
1158                         char))
1159         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1160         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1161         (#.+char-attr-package-delimiter+ (go INTERN))
1162         (t (go SYMBOL)))
1163       INTERN
1164       (setq colons 2)
1165       (setq char (read-char stream nil nil))
1166       (unless char
1167         (reader-eof-error stream "after reading a colon"))
1168       (case (char-class char attribute-array attribute-hash-table)
1169         (#.+char-attr-delimiter+
1170          (unread-char char stream)
1171          (%reader-error stream
1172                         "illegal terminating character after a colon: ~S"
1173                         char))
1174         (#.+char-attr-single-escape+ (go SINGLE-ESCAPE))
1175         (#.+char-attr-multiple-escape+ (go MULT-ESCAPE))
1176         (#.+char-attr-package-delimiter+
1177          (%reader-error stream
1178                         "too many colons after ~S name"
1179                         package-designator))
1180         (t (go SYMBOL)))
1181       RETURN-SYMBOL
1182       (casify-read-buffer escapes)
1183       (let ((found (if package-designator
1184                        (find-package package-designator)
1185                        (sane-package))))
1186         (unless found
1187           (error 'reader-package-error :stream stream
1188                  :format-arguments (list package-designator)
1189                  :format-control "package ~S not found"))
1190
1191         (if (or (zerop colons) (= colons 2) (eq found *keyword-package*))
1192             (return (intern* *read-buffer* *ouch-ptr* found))
1193             (multiple-value-bind (symbol test)
1194                 (find-symbol* *read-buffer* *ouch-ptr* found)
1195               (when (eq test :external) (return symbol))
1196               (let ((name (read-buffer-to-string)))
1197                 (with-simple-restart (continue "Use symbol anyway.")
1198                   (error 'reader-package-error :stream stream
1199                          :format-arguments (list name (package-name found))
1200                          :format-control
1201                          (if test
1202                              "The symbol ~S is not external in the ~A package."
1203                              "Symbol ~S not found in the ~A package.")))
1204                 (return (intern name found)))))))))
1205
1206 ;;; for semi-external use:
1207 ;;;
1208 ;;; For semi-external use: Return 3 values: the string for the token,
1209 ;;; a flag for whether there was an escape char, and the position of
1210 ;;; any package delimiter.
1211 (defun read-extended-token (stream &optional (*readtable* *readtable*))
1212   (let ((first-char (read-char stream nil nil t)))
1213     (cond (first-char
1214            (multiple-value-bind (escapes colon)
1215                (internal-read-extended-token stream first-char nil)
1216              (casify-read-buffer escapes)
1217              (values (read-buffer-to-string) (not (null escapes)) colon)))
1218           (t
1219            (values "" nil nil)))))
1220
1221 ;;; for semi-external use:
1222 ;;;
1223 ;;; Read an extended token with the first character escaped. Return
1224 ;;; the string for the token.
1225 (defun read-extended-token-escaped (stream &optional (*readtable* *readtable*))
1226   (let ((first-char (read-char stream nil nil)))
1227     (cond (first-char
1228             (let ((escapes (internal-read-extended-token stream first-char t)))
1229               (casify-read-buffer escapes)
1230               (read-buffer-to-string)))
1231           (t
1232             (reader-eof-error stream "after escape")))))
1233 \f
1234 ;;;; number-reading functions
1235
1236 (defmacro digit* nil
1237   `(do ((ch char (inch-read-buffer)))
1238        ((or (eofp ch) (not (digit-char-p ch))) (setq char ch))
1239      ;; Report if at least one digit is seen.
1240      (setq one-digit t)))
1241
1242 (defmacro exponent-letterp (letter)
1243   `(memq ,letter '(#\E #\S #\F #\L #\D #\e #\s #\f #\l #\d)))
1244
1245 ;;; FIXME: It would be cleaner to have these generated automatically
1246 ;;; by compile-time code instead of having them hand-created like
1247 ;;; this. The !COLD-INIT-INTEGER-READER code below should be resurrected
1248 ;;; and tested.
1249 (defvar *integer-reader-safe-digits*
1250   #(nil nil
1251     26 17 13 11 10 9 8 8 8 7 7 7 7 6 6 6 6 6 6 6 6 5 5 5 5 5 5 5 5 5 5 5 5 5 5)
1252   #!+sb-doc
1253   "the mapping of base to 'safe' number of digits to read for a fixnum")
1254 (defvar *integer-reader-base-power*
1255   #(nil nil
1256     67108864 129140163 67108864 48828125 60466176 40353607
1257     16777216 43046721 100000000 19487171 35831808 62748517 105413504 11390625
1258     16777216 24137569 34012224 47045881 64000000 85766121 113379904 6436343
1259     7962624 9765625 11881376 14348907 17210368 20511149 24300000 28629151
1260     33554432 39135393 45435424 52521875 60466176)
1261   #!+sb-doc
1262   "the largest fixnum power of the base for MAKE-INTEGER")
1263 (declaim (simple-vector *integer-reader-safe-digits*
1264                         *integer-reader-base-power*))
1265 #|
1266 (defun !cold-init-integer-reader ()
1267   (do ((base 2 (1+ base)))
1268       ((> base 36))
1269     (let ((digits
1270           (do ((fix (truncate most-positive-fixnum base)
1271                     (truncate fix base))
1272                (digits 0 (1+ digits)))
1273               ((zerop fix) digits))))
1274       (setf (aref *integer-reader-safe-digits* base)
1275             digits
1276             (aref *integer-reader-base-power* base)
1277             (expt base digits)))))
1278 |#
1279
1280 (defun make-integer ()
1281   #!+sb-doc
1282   "Minimizes bignum-fixnum multiplies by reading a 'safe' number of digits,
1283   then multiplying by a power of the base and adding."
1284   (let* ((base *read-base*)
1285          (digits-per (aref *integer-reader-safe-digits* base))
1286          (base-power (aref *integer-reader-base-power* base))
1287          (negativep nil)
1288          (number 0))
1289     (declare (type index digits-per base-power))
1290     (read-unwind-read-buffer)
1291     (let ((char (inch-read-buffer)))
1292       (cond ((char= char #\-)
1293              (setq negativep t))
1294             ((char= char #\+))
1295             (t (unread-buffer))))
1296     (loop
1297      (let ((num 0))
1298        (declare (type index num))
1299        (dotimes (digit digits-per)
1300          (let* ((ch (inch-read-buffer)))
1301            (cond ((or (eofp ch) (char= ch #\.))
1302                   (return-from make-integer
1303                                (let ((res
1304                                       (if (zerop number) num
1305                                           (+ num (* number
1306                                                     (expt base digit))))))
1307                                  (if negativep (- res) res))))
1308                  (t (setq num (+ (digit-char-p ch base)
1309                                  (the index (* num base))))))))
1310        (setq number (+ num (* number base-power)))))))
1311
1312 (defun make-float (stream)
1313   ;; Assume that the contents of *read-buffer* are a legal float, with nothing
1314   ;; else after it.
1315   (read-unwind-read-buffer)
1316   (let ((negative-fraction nil)
1317         (number 0)
1318         (divisor 1)
1319         (negative-exponent nil)
1320         (exponent 0)
1321         (float-char ())
1322         (char (inch-read-buffer)))
1323     (if (cond ((char= char #\+) t)
1324               ((char= char #\-) (setq negative-fraction t)))
1325         ;; Flush it.
1326         (setq char (inch-read-buffer)))
1327     ;; Read digits before the dot.
1328     (do* ((ch char (inch-read-buffer))
1329           (dig (digit-char-p ch) (digit-char-p ch)))
1330          ((not dig) (setq char ch))
1331       (setq number (+ (* number 10) dig)))
1332     ;; Deal with the dot, if it's there.
1333     (when (char= char #\.)
1334       (setq char (inch-read-buffer))
1335       ;; Read digits after the dot.
1336       (do* ((ch char (inch-read-buffer))
1337             (dig (and (not (eofp ch)) (digit-char-p ch))
1338                  (and (not (eofp ch)) (digit-char-p ch))))
1339            ((not dig) (setq char ch))
1340         (setq divisor (* divisor 10))
1341         (setq number (+ (* number 10) dig))))
1342     ;; Is there an exponent letter?
1343     (cond ((eofp char)
1344            ;; If not, we've read the whole number.
1345            (let ((num (make-float-aux number divisor
1346                                       *read-default-float-format*
1347                                       stream)))
1348              (return-from make-float (if negative-fraction (- num) num))))
1349           ((exponent-letterp char)
1350            (setq float-char char)
1351            ;; Build exponent.
1352            (setq char (inch-read-buffer))
1353            ;; Check leading sign.
1354            (if (cond ((char= char #\+) t)
1355                      ((char= char #\-) (setq negative-exponent t)))
1356                ;; Flush sign.
1357                (setq char (inch-read-buffer)))
1358            ;; Read digits for exponent.
1359            (do* ((ch char (inch-read-buffer))
1360                  (dig (and (not (eofp ch)) (digit-char-p ch))
1361                       (and (not (eofp ch)) (digit-char-p ch))))
1362                 ((not dig)
1363                  (setq exponent (if negative-exponent (- exponent) exponent)))
1364              (setq exponent (+ (* exponent 10) dig)))
1365            ;; Generate and return the float, depending on FLOAT-CHAR:
1366            (let* ((float-format (case (char-upcase float-char)
1367                                   (#\E *read-default-float-format*)
1368                                   (#\S 'short-float)
1369                                   (#\F 'single-float)
1370                                   (#\D 'double-float)
1371                                   (#\L 'long-float)))
1372                   (result (make-float-aux (* (expt 10 exponent) number)
1373                                           divisor float-format stream)))
1374              (return-from make-float
1375                (if negative-fraction (- result) result))))
1376           (t (bug "bad fallthrough in floating point reader")))))
1377
1378 (defun make-float-aux (number divisor float-format stream)
1379   (handler-case
1380       (coerce (/ number divisor) float-format)
1381     (type-error (c)
1382       (error 'reader-impossible-number-error
1383              :error c :stream stream
1384              :format-control "failed to build float"))))
1385
1386 (defun make-ratio (stream)
1387   ;; Assume *READ-BUFFER* contains a legal ratio. Build the number from
1388   ;; the string.
1389   ;;
1390   ;; Look for optional "+" or "-".
1391   (let ((numerator 0) (denominator 0) (char ()) (negative-number nil))
1392     (read-unwind-read-buffer)
1393     (setq char (inch-read-buffer))
1394     (cond ((char= char #\+)
1395            (setq char (inch-read-buffer)))
1396           ((char= char #\-)
1397            (setq char (inch-read-buffer))
1398            (setq negative-number t)))
1399     ;; Get numerator.
1400     (do* ((ch char (inch-read-buffer))
1401           (dig (digit-char-p ch *read-base*)
1402                (digit-char-p ch *read-base*)))
1403          ((not dig))
1404          (setq numerator (+ (* numerator *read-base*) dig)))
1405     ;; Get denominator.
1406     (do* ((ch (inch-read-buffer) (inch-read-buffer))
1407           (dig ()))
1408          ((or (eofp ch) (not (setq dig (digit-char-p ch *read-base*)))))
1409          (setq denominator (+ (* denominator *read-base*) dig)))
1410     (let ((num (handler-case
1411                    (/ numerator denominator)
1412                  (arithmetic-error (c)
1413                    (error 'reader-impossible-number-error
1414                           :error c :stream stream
1415                           :format-control "failed to build ratio")))))
1416       (if negative-number (- num) num))))
1417 \f
1418 ;;;; cruft for dispatch macros
1419
1420 (defun make-char-dispatch-table ()
1421   (make-hash-table))
1422
1423 (defun dispatch-char-error (stream sub-char ignore)
1424   (declare (ignore ignore))
1425   (if *read-suppress*
1426       (values)
1427       (%reader-error stream "no dispatch function defined for ~S" sub-char)))
1428
1429 (defun make-dispatch-macro-character (char &optional
1430                                            (non-terminating-p nil)
1431                                            (rt *readtable*))
1432   #!+sb-doc
1433   "Cause CHAR to become a dispatching macro character in readtable (which
1434    defaults to the current readtable). If NON-TERMINATING-P, the char will
1435    be non-terminating."
1436   (set-macro-character char #'read-dispatch-char non-terminating-p rt)
1437   (let* ((dalist (dispatch-tables rt))
1438          (dtable (cdr (find char dalist :test #'char= :key #'car))))
1439     (cond (dtable
1440            (error "The dispatch character ~S already exists." char))
1441           (t
1442            (setf (dispatch-tables rt)
1443                  (push (cons char (make-char-dispatch-table)) dalist)))))
1444   t)
1445
1446 (defun set-dispatch-macro-character (disp-char sub-char function
1447                                                &optional (rt *readtable*))
1448   #!+sb-doc
1449   "Cause FUNCTION to be called whenever the reader reads DISP-CHAR
1450    followed by SUB-CHAR."
1451   ;; Get the dispatch char for macro (error if not there), diddle
1452   ;; entry for sub-char.
1453   (when (digit-char-p sub-char)
1454     (error "SUB-CHAR must not be a decimal digit: ~S" sub-char))
1455   (let* ((sub-char (char-upcase sub-char))
1456          (rt (or rt *standard-readtable*))
1457          (dpair (find disp-char (dispatch-tables rt)
1458                       :test #'char= :key #'car)))
1459     (if dpair
1460         (setf (gethash sub-char (cdr dpair)) (coerce function 'function))
1461         (error "~S is not a dispatch char." disp-char))))
1462
1463 (defun get-dispatch-macro-character (disp-char sub-char
1464                                      &optional (rt *readtable*))
1465   #!+sb-doc
1466   "Return the macro character function for SUB-CHAR under DISP-CHAR
1467    or NIL if there is no associated function."
1468   (let* ((sub-char (char-upcase sub-char))
1469          (rt (or rt *standard-readtable*))
1470          (dpair (find disp-char (dispatch-tables rt)
1471                       :test #'char= :key #'car)))
1472     (if dpair
1473         (values (gethash sub-char (cdr dpair)))
1474         (error "~S is not a dispatch char." disp-char))))
1475
1476 (defun read-dispatch-char (stream char)
1477   ;; Read some digits.
1478   (let ((numargp nil)
1479         (numarg 0)
1480         (sub-char ()))
1481     (do* ((ch (read-char stream nil *eof-object*)
1482               (read-char stream nil *eof-object*))
1483           (dig ()))
1484          ((or (eofp ch)
1485               (not (setq dig (digit-char-p ch))))
1486           ;; Take care of the extra char.
1487           (if (eofp ch)
1488               (reader-eof-error stream "inside dispatch character")
1489               (setq sub-char (char-upcase ch))))
1490       (setq numargp t)
1491       (setq numarg (+ (* numarg 10) dig)))
1492     ;; Look up the function and call it.
1493     (let ((dpair (find char (dispatch-tables *readtable*)
1494                        :test #'char= :key #'car)))
1495       (if dpair
1496           (funcall (the function
1497                      (gethash sub-char (cdr dpair) #'dispatch-char-error))
1498                    stream sub-char (if numargp numarg nil))
1499           (%reader-error stream "no dispatch table for dispatch char")))))
1500 \f
1501 ;;;; READ-FROM-STRING
1502
1503 (defun read-from-string (string &optional (eof-error-p t) eof-value
1504                                 &key (start 0) end
1505                                 preserve-whitespace)
1506   #!+sb-doc
1507   "The characters of string are successively given to the lisp reader
1508    and the lisp object built by the reader is returned. Macro chars
1509    will take effect."
1510   (declare (string string))
1511   (with-array-data ((string string :offset-var offset)
1512                     (start start)
1513                     (end (%check-vector-sequence-bounds string start end)))
1514     (let ((stream (make-string-input-stream string start end)))
1515       (values (if preserve-whitespace
1516                   (read-preserving-whitespace stream eof-error-p eof-value)
1517                   (read stream eof-error-p eof-value))
1518               (- (string-input-stream-current stream) offset)))))
1519 \f
1520 ;;;; PARSE-INTEGER
1521
1522 (defun parse-integer (string &key (start 0) end (radix 10) junk-allowed)
1523   #!+sb-doc
1524   "Examine the substring of string delimited by start and end
1525   (default to the beginning and end of the string)  It skips over
1526   whitespace characters and then tries to parse an integer. The
1527   radix parameter must be between 2 and 36."
1528   (macrolet ((parse-error (format-control)
1529                `(error 'simple-parse-error
1530                        :format-control ,format-control
1531                        :format-arguments (list string))))
1532     (with-array-data ((string string :offset-var offset)
1533                       (start start)
1534                       (end (%check-vector-sequence-bounds string start end)))
1535       (let ((index (do ((i start (1+ i)))
1536                        ((= i end)
1537                         (if junk-allowed
1538                             (return-from parse-integer (values nil end))
1539                             (parse-error "no non-whitespace characters in string ~S.")))
1540                      (declare (fixnum i))
1541                      (unless (whitespace[1]p (char string i)) (return i))))
1542             (minusp nil)
1543             (found-digit nil)
1544             (result 0))
1545         (declare (fixnum index))
1546         (let ((char (char string index)))
1547           (cond ((char= char #\-)
1548                  (setq minusp t)
1549                  (incf index))
1550                 ((char= char #\+)
1551                  (incf index))))
1552         (loop
1553          (when (= index end) (return nil))
1554          (let* ((char (char string index))
1555                 (weight (digit-char-p char radix)))
1556            (cond (weight
1557                   (setq result (+ weight (* result radix))
1558                         found-digit t))
1559                  (junk-allowed (return nil))
1560                  ((whitespace[1]p char)
1561                   (loop
1562                    (incf index)
1563                    (when (= index end) (return))
1564                    (unless (whitespace[1]p (char string index))
1565                       (parse-error "junk in string ~S")))
1566                   (return nil))
1567                  (t
1568                   (parse-error "junk in string ~S"))))
1569          (incf index))
1570         (values
1571          (if found-digit
1572              (if minusp (- result) result)
1573              (if junk-allowed
1574                  nil
1575                  (parse-error "no digits in string ~S")))
1576          (- index offset))))))
1577 \f
1578 ;;;; reader initialization code
1579
1580 (defun !reader-cold-init ()
1581   (!cold-init-constituent-trait-table)
1582   (!cold-init-standard-readtable)
1583   ;; FIXME: This was commented out, but should probably be restored.
1584   #+nil (!cold-init-integer-reader))
1585 \f
1586 (def!method print-object ((readtable readtable) stream)
1587   (print-unreadable-object (readtable stream :identity t :type t)))