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