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