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