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