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