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