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