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