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