0.9.2.3:
[sbcl.git] / src / code / fd-stream.lisp
1 ;;;; streams for UNIX file descriptors
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
14 ;;;; buffer manipulation routines
15
16 ;;; FIXME: Is it really good to maintain this pool separate from the
17 ;;; GC and the C malloc logic?
18 (defvar *available-buffers* ()
19   #!+sb-doc
20   "List of available buffers. Each buffer is an sap pointing to
21   bytes-per-buffer of memory.")
22
23 (defconstant bytes-per-buffer (* 4 1024)
24   #!+sb-doc
25   "Number of bytes per buffer.")
26
27 ;;; Return the next available buffer, creating one if necessary.
28 #!-sb-fluid (declaim (inline next-available-buffer))
29 (defun next-available-buffer ()
30   (if *available-buffers*
31       (pop *available-buffers*)
32       (allocate-system-memory bytes-per-buffer)))
33 \f
34 ;;;; the FD-STREAM structure
35
36 (defstruct (fd-stream
37             (:constructor %make-fd-stream)
38             (:conc-name fd-stream-)
39             (:predicate fd-stream-p)
40             (:include ansi-stream
41                       (misc #'fd-stream-misc-routine))
42             (:copier nil))
43
44   ;; the name of this stream
45   (name nil)
46   ;; the file this stream is for
47   (file nil)
48   ;; the backup file namestring for the old file, for :IF-EXISTS
49   ;; :RENAME or :RENAME-AND-DELETE.
50   (original nil :type (or simple-string null))
51   (delete-original nil)       ; for :if-exists :rename-and-delete
52   ;;; the number of bytes per element
53   (element-size 1 :type index)
54   ;; the type of element being transfered
55   (element-type 'base-char)   
56   ;; the Unix file descriptor
57   (fd -1 :type fixnum)        
58   ;; controls when the output buffer is flushed
59   (buffering :full :type (member :full :line :none))
60   ;; controls whether the input buffer must be cleared before output
61   ;; (must be done for files, not for sockets, pipes and other data
62   ;; sources where input and output aren't related).  non-NIL means
63   ;; don't clear input buffer.
64   (dual-channel-p nil)
65   ;; character position (if known)
66   (char-pos nil :type (or index null))
67   ;; T if input is waiting on FD. :EOF if we hit EOF.
68   (listen nil :type (member nil t :eof))
69
70   ;; the input buffer
71   (unread nil)
72   (ibuf-sap nil :type (or system-area-pointer null))
73   (ibuf-length nil :type (or index null))
74   (ibuf-head 0 :type index)
75   (ibuf-tail 0 :type index)
76
77   ;; the output buffer
78   (obuf-sap nil :type (or system-area-pointer null))
79   (obuf-length nil :type (or index null))
80   (obuf-tail 0 :type index)
81
82   ;; output flushed, but not written due to non-blocking io?
83   (output-later nil)
84   (handler nil)
85   ;; timeout specified for this stream, or NIL if none
86   (timeout nil :type (or index null))
87   ;; pathname of the file this stream is opened to (returned by PATHNAME)
88   (pathname nil :type (or pathname null))
89   (external-format :default)
90   (output-bytes #'ill-out :type function))
91 (def!method print-object ((fd-stream fd-stream) stream)
92   (declare (type stream stream))
93   (print-unreadable-object (fd-stream stream :type t :identity t)
94     (format stream "for ~S" (fd-stream-name fd-stream))))
95 \f
96 ;;;; output routines and related noise
97
98 (defvar *output-routines* ()
99   #!+sb-doc
100   "List of all available output routines. Each element is a list of the
101   element-type output, the kind of buffering, the function name, and the number
102   of bytes per element.")
103
104 ;;; common idioms for reporting low-level stream and file problems
105 (defun simple-stream-perror (note-format stream errno)
106   (error 'simple-stream-error
107          :stream stream
108          :format-control "~@<~?: ~2I~_~A~:>"
109          :format-arguments (list note-format (list stream) (strerror errno))))
110 (defun simple-file-perror (note-format pathname errno)
111   (error 'simple-file-error
112          :pathname pathname
113          :format-control "~@<~?: ~2I~_~A~:>"
114          :format-arguments
115          (list note-format (list pathname) (strerror errno))))
116
117 (defun stream-decoding-error (stream octets)
118   (error 'stream-decoding-error
119          :stream stream
120          ;; FIXME: dunno how to get at OCTETS currently, or even if
121          ;; that's the right thing to report.
122          :octets octets))
123 (defun stream-encoding-error (stream code)
124   (error 'stream-encoding-error
125          :stream stream
126          :code code))
127
128 ;;; Returning true goes into end of file handling, false will enter another
129 ;;; round of input buffer filling followed by re-entering character decode.
130 (defun stream-decoding-error-and-handle (stream octet-count)
131   (restart-case
132       (stream-decoding-error stream
133                              (let ((sap (fd-stream-ibuf-sap stream))
134                                    (head (fd-stream-ibuf-head stream)))
135                                (loop for i from 0 below octet-count
136                                      collect (sap-ref-8 sap (+ head i)))))
137     (attempt-resync ()
138       :report (lambda (stream)
139                 (format stream
140                         "~@<Attempt to resync the stream at a character ~
141                         character boundary and continue.~@:>"))
142       (fd-stream-resync stream)
143       nil)
144     (force-end-of-file ()
145       :report (lambda (stream)
146                 (format stream "~@<Force an end of file.~@:>"))
147       t)))
148
149 (defun stream-encoding-error-and-handle (stream code)
150   (restart-case
151       (stream-encoding-error stream code)
152     (output-nothing ()
153       :report (lambda (stream)
154                 (format stream "~@<Skip output of this character.~@:>"))
155       (throw 'output-nothing nil))))
156
157 ;;; This is called by the server when we can write to the given file
158 ;;; descriptor. Attempt to write the data again. If it worked, remove
159 ;;; the data from the OUTPUT-LATER list. If it didn't work, something
160 ;;; is wrong.
161 (defun frob-output-later (stream)
162   (let* ((stuff (pop (fd-stream-output-later stream)))
163          (base (car stuff))
164          (start (cadr stuff))
165          (end (caddr stuff))
166          (reuse-sap (cadddr stuff))
167          (length (- end start)))
168     (declare (type index start end length))
169     (multiple-value-bind (count errno)
170         (sb!unix:unix-write (fd-stream-fd stream)
171                             base
172                             start
173                             length)
174       (cond ((not count)
175              (if (= errno sb!unix:ewouldblock)
176                  (error "Write would have blocked, but SERVER told us to go.")
177                  (simple-stream-perror "couldn't write to ~S" stream errno)))
178             ((eql count length) ; Hot damn, it worked.
179              (when reuse-sap
180                (push base *available-buffers*)))
181             ((not (null count)) ; sorta worked..
182              (push (list base
183                          (the index (+ start count))
184                          end)
185                    (fd-stream-output-later stream))))))
186   (unless (fd-stream-output-later stream)
187     (sb!sys:remove-fd-handler (fd-stream-handler stream))
188     (setf (fd-stream-handler stream) nil)))
189
190 ;;; Arange to output the string when we can write on the file descriptor.
191 (defun output-later (stream base start end reuse-sap)
192   (cond ((null (fd-stream-output-later stream))
193          (setf (fd-stream-output-later stream)
194                (list (list base start end reuse-sap)))
195          (setf (fd-stream-handler stream)
196                (sb!sys:add-fd-handler (fd-stream-fd stream)
197                                       :output
198                                       (lambda (fd)
199                                         (declare (ignore fd))
200                                         (frob-output-later stream)))))
201         (t
202          (nconc (fd-stream-output-later stream)
203                 (list (list base start end reuse-sap)))))
204   (when reuse-sap
205     (let ((new-buffer (next-available-buffer)))
206       (setf (fd-stream-obuf-sap stream) new-buffer)
207       (setf (fd-stream-obuf-length stream) bytes-per-buffer))))
208
209 ;;; Output the given noise. Check to see whether there are any pending
210 ;;; writes. If so, just queue this one. Otherwise, try to write it. If
211 ;;; this would block, queue it.
212 (defun frob-output (stream base start end reuse-sap)
213   (declare (type fd-stream stream)
214            (type (or system-area-pointer (simple-array * (*))) base)
215            (type index start end))
216   (if (not (null (fd-stream-output-later stream))) ; something buffered.
217       (progn
218         (output-later stream base start end reuse-sap)
219         ;; ### check to see whether any of this noise can be output
220         )
221       (let ((length (- end start)))
222         (multiple-value-bind (count errno)
223             (sb!unix:unix-write (fd-stream-fd stream) base start length)
224           (cond ((not count)
225                  (if (= errno sb!unix:ewouldblock)
226                      (output-later stream base start end reuse-sap)
227                      (simple-stream-perror "couldn't write to ~S"
228                                            stream
229                                            errno)))
230                 ((not (eql count length))
231                  (output-later stream base (the index (+ start count))
232                                end reuse-sap)))))))
233
234 ;;; Flush any data in the output buffer.
235 (defun flush-output-buffer (stream)
236   (let ((length (fd-stream-obuf-tail stream)))
237     (unless (= length 0)
238       (frob-output stream (fd-stream-obuf-sap stream) 0 length t)
239       (setf (fd-stream-obuf-tail stream) 0))))
240
241 (defmacro output-wrapper/variable-width ((stream size buffering restart)
242                                          &body body)
243   (let ((stream-var (gensym)))
244     `(let ((,stream-var ,stream)
245            (size ,size))
246       ,(unless (eq (car buffering) :none)
247          `(when (< (fd-stream-obuf-length ,stream-var)
248                    (+ (fd-stream-obuf-tail ,stream-var)
249                        size))
250             (flush-output-buffer ,stream-var)))
251       ,(unless (eq (car buffering) :none)
252          `(when (and (not (fd-stream-dual-channel-p ,stream-var))
253                      (> (fd-stream-ibuf-tail ,stream-var)
254                         (fd-stream-ibuf-head ,stream-var)))
255             (file-position ,stream-var (file-position ,stream-var))))
256       ,(if restart
257            `(catch 'output-nothing
258               ,@body
259               (incf (fd-stream-obuf-tail ,stream-var) size))
260            `(progn
261              ,@body
262              (incf (fd-stream-obuf-tail ,stream-var) size)))
263       ,(ecase (car buffering)
264          (:none
265           `(flush-output-buffer ,stream-var))
266          (:line
267           `(when (eq (char-code byte) (char-code #\Newline))
268              (flush-output-buffer ,stream-var)))
269          (:full))
270     (values))))
271
272 (defmacro output-wrapper ((stream size buffering restart) &body body)
273   (let ((stream-var (gensym)))
274     `(let ((,stream-var ,stream))
275       ,(unless (eq (car buffering) :none)
276          `(when (< (fd-stream-obuf-length ,stream-var)
277                    (+ (fd-stream-obuf-tail ,stream-var)
278                        ,size))
279             (flush-output-buffer ,stream-var)))
280       ,(unless (eq (car buffering) :none)
281          `(when (and (not (fd-stream-dual-channel-p ,stream-var))
282                      (> (fd-stream-ibuf-tail ,stream-var)
283                         (fd-stream-ibuf-head ,stream-var)))
284             (file-position ,stream-var (file-position ,stream-var))))
285       ,(if restart
286            `(catch 'output-nothing
287               ,@body
288               (incf (fd-stream-obuf-tail ,stream-var) ,size))
289            `(progn
290              ,@body
291              (incf (fd-stream-obuf-tail ,stream-var) ,size)))
292       ,(ecase (car buffering)
293          (:none
294           `(flush-output-buffer ,stream-var))
295          (:line
296           `(when (eq (char-code byte) (char-code #\Newline))
297              (flush-output-buffer ,stream-var)))
298          (:full))
299     (values))))
300
301 (defmacro def-output-routines/variable-width
302     ((name-fmt size restart external-format &rest bufferings)
303      &body body)
304   (declare (optimize (speed 1)))
305   (cons 'progn
306         (mapcar
307             (lambda (buffering)
308               (let ((function
309                      (intern (format nil name-fmt (string (car buffering))))))
310                 `(progn
311                    (defun ,function (stream byte)
312                      (output-wrapper/variable-width (stream ,size ,buffering ,restart)
313                        ,@body))
314                    (setf *output-routines*
315                          (nconc *output-routines*
316                                 ',(mapcar
317                                    (lambda (type)
318                                      (list type
319                                            (car buffering)
320                                            function
321                                            1
322                                            external-format))
323                                    (cdr buffering)))))))
324             bufferings)))
325
326 ;;; Define output routines that output numbers SIZE bytes long for the
327 ;;; given bufferings. Use BODY to do the actual output.
328 (defmacro def-output-routines ((name-fmt size restart &rest bufferings)
329                                &body body)
330   (declare (optimize (speed 1)))
331   (cons 'progn
332         (mapcar
333             (lambda (buffering)
334               (let ((function
335                      (intern (format nil name-fmt (string (car buffering))))))
336                 `(progn
337                    (defun ,function (stream byte)
338                      (output-wrapper (stream ,size ,buffering ,restart)
339                        ,@body))
340                    (setf *output-routines*
341                          (nconc *output-routines*
342                                 ',(mapcar
343                                    (lambda (type)
344                                      (list type
345                                            (car buffering)
346                                            function
347                                            size
348                                            nil))
349                                    (cdr buffering)))))))
350             bufferings)))
351
352 ;;; FIXME: is this used anywhere any more?
353 (def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
354                       1
355                       t
356                       (:none character)
357                       (:line character)
358                       (:full character))
359   (if (char= byte #\Newline)
360       (setf (fd-stream-char-pos stream) 0)
361       (incf (fd-stream-char-pos stream)))
362   (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
363         (char-code byte)))
364
365 (def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
366                       1
367                       nil
368                       (:none (unsigned-byte 8))
369                       (:full (unsigned-byte 8)))
370   (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
371         byte))
372
373 (def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
374                       1
375                       nil
376                       (:none (signed-byte 8))
377                       (:full (signed-byte 8)))
378   (setf (signed-sap-ref-8 (fd-stream-obuf-sap stream)
379                           (fd-stream-obuf-tail stream))
380         byte))
381
382 (def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
383                       2
384                       nil
385                       (:none (unsigned-byte 16))
386                       (:full (unsigned-byte 16)))
387   (setf (sap-ref-16 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
388         byte))
389
390 (def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
391                       2
392                       nil
393                       (:none (signed-byte 16))
394                       (:full (signed-byte 16)))
395   (setf (signed-sap-ref-16 (fd-stream-obuf-sap stream)
396                            (fd-stream-obuf-tail stream))
397         byte))
398
399 (def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
400                       4
401                       nil
402                       (:none (unsigned-byte 32))
403                       (:full (unsigned-byte 32)))
404   (setf (sap-ref-32 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
405         byte))
406
407 (def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
408                       4
409                       nil
410                       (:none (signed-byte 32))
411                       (:full (signed-byte 32)))
412   (setf (signed-sap-ref-32 (fd-stream-obuf-sap stream)
413                            (fd-stream-obuf-tail stream))
414         byte))
415
416 ;;; Do the actual output. If there is space to buffer the string,
417 ;;; buffer it. If the string would normally fit in the buffer, but
418 ;;; doesn't because of other stuff in the buffer, flush the old noise
419 ;;; out of the buffer and put the string in it. Otherwise we have a
420 ;;; very long string, so just send it directly (after flushing the
421 ;;; buffer, of course).
422 (defun output-raw-bytes (fd-stream thing &optional start end)
423   #!+sb-doc
424   "Output THING to FD-STREAM. THING can be any kind of vector or a SAP. If
425   THING is a SAP, END must be supplied (as length won't work)."
426   (let ((start (or start 0))
427         (end (or end (length (the (simple-array * (*)) thing)))))
428     (declare (type index start end))
429     (when (and (not (fd-stream-dual-channel-p fd-stream))
430                (> (fd-stream-ibuf-tail fd-stream)
431                   (fd-stream-ibuf-head fd-stream)))
432       (file-position fd-stream (file-position fd-stream)))
433     (let* ((len (fd-stream-obuf-length fd-stream))
434            (tail (fd-stream-obuf-tail fd-stream))
435            (space (- len tail))
436            (bytes (- end start))
437            (newtail (+ tail bytes)))
438       (cond ((minusp bytes) ; error case
439              (error ":END before :START!"))
440             ((zerop bytes)) ; easy case
441             ((<= bytes space)
442              (if (system-area-pointer-p thing)
443                  (system-area-ub8-copy thing start
444                                        (fd-stream-obuf-sap fd-stream)
445                                        tail
446                                        bytes)
447                  ;; FIXME: There should be some type checking somewhere to
448                  ;; verify that THING here is a vector, not just <not a SAP>.
449                  (copy-ub8-to-system-area thing start
450                                           (fd-stream-obuf-sap fd-stream)
451                                           tail
452                                           bytes))
453              (setf (fd-stream-obuf-tail fd-stream) newtail))
454             ((<= bytes len)
455              (flush-output-buffer fd-stream)
456              (if (system-area-pointer-p thing)
457                  (system-area-ub8-copy thing
458                                        start
459                                        (fd-stream-obuf-sap fd-stream)
460                                        0
461                                        bytes)
462                  ;; FIXME: There should be some type checking somewhere to
463                  ;; verify that THING here is a vector, not just <not a SAP>.
464                  (copy-ub8-to-system-area thing
465                                           start
466                                           (fd-stream-obuf-sap fd-stream)
467                                           0
468                                           bytes))
469              (setf (fd-stream-obuf-tail fd-stream) bytes))
470             (t
471              (flush-output-buffer fd-stream)
472              (frob-output fd-stream thing start end nil))))))
473
474 ;;; the routine to use to output a string. If the stream is
475 ;;; unbuffered, slam the string down the file descriptor, otherwise
476 ;;; use OUTPUT-RAW-BYTES to buffer the string. Update charpos by
477 ;;; checking to see where the last newline was.
478 ;;;
479 ;;; Note: some bozos (the FASL dumper) call write-string with things
480 ;;; other than strings. Therefore, we must make sure we have a string
481 ;;; before calling POSITION on it.
482 ;;; KLUDGE: It would be better to fix the bozos instead of trying to
483 ;;; cover for them here. -- WHN 20000203
484 (defun fd-sout (stream thing start end)
485   (let ((start (or start 0))
486         (end (or end (length (the vector thing)))))
487     (declare (fixnum start end))
488     (if (stringp thing)
489         (let ((last-newline (and (find #\newline (the simple-string thing)
490                                        :start start :end end)
491                                  ;; FIXME why do we need both calls?
492                                  ;; Is find faster forwards than
493                                  ;; position is backwards?
494                                  (position #\newline (the simple-string thing)
495                                            :from-end t
496                                            :start start
497                                            :end end))))
498           (if (and (typep thing 'base-string)
499                    (eq (fd-stream-external-format stream) :latin-1))
500               (ecase (fd-stream-buffering stream)
501                 (:full
502                  (output-raw-bytes stream thing start end))
503                 (:line
504                  (output-raw-bytes stream thing start end)
505                  (when last-newline
506                    (flush-output-buffer stream)))
507                 (:none
508                  (frob-output stream thing start end nil)))
509               (ecase (fd-stream-buffering stream)
510                 (:full (funcall (fd-stream-output-bytes stream)
511                                 stream thing nil start end))
512                 (:line (funcall (fd-stream-output-bytes stream)
513                                 stream thing last-newline start end))
514                 (:none (funcall (fd-stream-output-bytes stream)
515                                 stream thing t start end))))
516           (if last-newline
517               (setf (fd-stream-char-pos stream)
518                     (- end last-newline 1))
519               (incf (fd-stream-char-pos stream)
520                     (- end start))))
521         (ecase (fd-stream-buffering stream)
522           ((:line :full)
523            (output-raw-bytes stream thing start end))
524           (:none
525            (frob-output stream thing start end nil))))))
526
527 (defvar *external-formats* ()
528   #!+sb-doc
529   "List of all available external formats. Each element is a list of the
530   element-type, string input function name, character input function name,
531   and string output function name.")
532
533 ;;; Find an output routine to use given the type and buffering. Return
534 ;;; as multiple values the routine, the real type transfered, and the
535 ;;; number of bytes per element.
536 (defun pick-output-routine (type buffering &optional external-format)
537   (when (subtypep type 'character)
538     (dolist (entry *external-formats*)
539       (when (member external-format (first entry))
540         (return-from pick-output-routine
541           (values (symbol-function (nth (ecase buffering
542                                           (:none 4)
543                                           (:line 5)
544                                           (:full 6))
545                                         entry))
546                   'character
547                   1
548                   (symbol-function (fourth entry))
549                   (first (first entry)))))))
550   (dolist (entry *output-routines*)
551     (when (and (subtypep type (first entry))
552                (eq buffering (second entry))
553                (or (not (fifth entry))
554                    (eq external-format (fifth entry))))
555       (return-from pick-output-routine
556         (values (symbol-function (third entry))
557                 (first entry)
558                 (fourth entry)))))
559   ;; KLUDGE: dealing with the buffering here leads to excessive code
560   ;; explosion.
561   ;;
562   ;; KLUDGE: also see comments in PICK-INPUT-ROUTINE
563   (loop for i from 40 by 8 to 1024 ; ARB (KLUDGE)
564         if (subtypep type `(unsigned-byte ,i))
565         do (return-from pick-output-routine
566              (values
567               (ecase buffering
568                 (:none
569                  (lambda (stream byte)
570                    (output-wrapper (stream (/ i 8) (:none) nil)
571                      (loop for j from 0 below (/ i 8)
572                            do (setf (sap-ref-8 
573                                      (fd-stream-obuf-sap stream)
574                                      (+ j (fd-stream-obuf-tail stream)))
575                                     (ldb (byte 8 (- i 8 (* j 8))) byte))))))
576                 (:full
577                  (lambda (stream byte)
578                    (output-wrapper (stream (/ i 8) (:full) nil)
579                      (loop for j from 0 below (/ i 8)
580                            do (setf (sap-ref-8 
581                                      (fd-stream-obuf-sap stream)
582                                      (+ j (fd-stream-obuf-tail stream)))
583                                     (ldb (byte 8 (- i 8 (* j 8))) byte)))))))
584               `(unsigned-byte ,i)
585               (/ i 8))))
586   (loop for i from 40 by 8 to 1024 ; ARB (KLUDGE)
587         if (subtypep type `(signed-byte ,i))
588         do (return-from pick-output-routine
589              (values
590               (ecase buffering
591                 (:none
592                  (lambda (stream byte)
593                    (output-wrapper (stream (/ i 8) (:none) nil)
594                      (loop for j from 0 below (/ i 8)
595                            do (setf (sap-ref-8 
596                                      (fd-stream-obuf-sap stream)
597                                      (+ j (fd-stream-obuf-tail stream)))
598                                     (ldb (byte 8 (- i 8 (* j 8))) byte))))))
599                 (:full
600                  (lambda (stream byte)
601                    (output-wrapper (stream (/ i 8) (:full) nil)
602                      (loop for j from 0 below (/ i 8)
603                            do (setf (sap-ref-8 
604                                      (fd-stream-obuf-sap stream)
605                                      (+ j (fd-stream-obuf-tail stream)))
606                                     (ldb (byte 8 (- i 8 (* j 8))) byte)))))))
607               `(signed-byte ,i)
608               (/ i 8)))))
609 \f
610 ;;;; input routines and related noise
611
612 ;;; a list of all available input routines. Each element is a list of
613 ;;; the element-type input, the function name, and the number of bytes
614 ;;; per element.
615 (defvar *input-routines* ())
616
617 ;;; Fill the input buffer, and return the number of bytes read. Throw
618 ;;; to EOF-INPUT-CATCHER if the eof was reached. Drop into
619 ;;; SYSTEM:SERVER if necessary.
620 (defun refill-buffer/fd (stream)
621   (let ((fd (fd-stream-fd stream))
622         (ibuf-sap (fd-stream-ibuf-sap stream))
623         (buflen (fd-stream-ibuf-length stream))
624         (head (fd-stream-ibuf-head stream))
625         (tail (fd-stream-ibuf-tail stream)))
626     (declare (type index head tail))
627     (unless (zerop head)
628       (cond ((eql head tail)
629              (setf head 0)
630              (setf tail 0)
631              (setf (fd-stream-ibuf-head stream) 0)
632              (setf (fd-stream-ibuf-tail stream) 0))
633             (t
634              (decf tail head)
635              (system-area-ub8-copy ibuf-sap head
636                                    ibuf-sap 0 tail)
637              (setf head 0)
638              (setf (fd-stream-ibuf-head stream) 0)
639              (setf (fd-stream-ibuf-tail stream) tail))))
640     (setf (fd-stream-listen stream) nil)
641     (multiple-value-bind (count errno)
642         ;; FIXME: Judging from compiler warnings, this WITH-ALIEN form expands
643         ;; into something which uses the not-yet-defined type
644         ;;   (SB!ALIEN-INTERNALS:ALIEN (* (SB!ALIEN:STRUCT SB!UNIX:FD-SET))).
645         ;; This is probably inefficient and unsafe and generally bad, so
646         ;; try to find some way to make that type known before
647         ;; this is compiled.
648         (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set)))
649           (sb!unix:fd-zero read-fds)
650           (sb!unix:fd-set fd read-fds)
651           (sb!unix:unix-fast-select (1+ fd)
652                                     (sb!alien:addr read-fds)
653                                     nil
654                                     nil
655                                     0
656                                     0))
657       (case count
658         (1)
659         (0
660          (unless (sb!sys:wait-until-fd-usable
661                   fd :input (fd-stream-timeout stream))
662            (error 'io-timeout :stream stream :direction :read)))
663         (t
664          (simple-stream-perror "couldn't check whether ~S is readable"
665                                stream
666                                errno))))
667     (multiple-value-bind (count errno)
668         (sb!unix:unix-read fd
669                            (sb!sys:int-sap (+ (sb!sys:sap-int ibuf-sap) tail))
670                            (- buflen tail))
671       (cond ((null count)
672              (if (eql errno sb!unix:ewouldblock)
673                  (progn
674                    (unless (sb!sys:wait-until-fd-usable
675                             fd :input (fd-stream-timeout stream))
676                      (error 'io-timeout :stream stream :direction :read))
677                    (refill-buffer/fd stream))
678                  (simple-stream-perror "couldn't read from ~S" stream errno)))
679             ((zerop count)
680              (setf (fd-stream-listen stream) :eof)
681              (/show0 "THROWing EOF-INPUT-CATCHER")
682              (throw 'eof-input-catcher nil))
683             (t
684              (incf (fd-stream-ibuf-tail stream) count)
685              count)))))
686                         
687 ;;; Make sure there are at least BYTES number of bytes in the input
688 ;;; buffer. Keep calling REFILL-BUFFER/FD until that condition is met.
689 (defmacro input-at-least (stream bytes)
690   (let ((stream-var (gensym))
691         (bytes-var (gensym)))
692     `(let ((,stream-var ,stream)
693            (,bytes-var ,bytes))
694        (loop
695          (when (>= (- (fd-stream-ibuf-tail ,stream-var)
696                       (fd-stream-ibuf-head ,stream-var))
697                    ,bytes-var)
698            (return))
699          (refill-buffer/fd ,stream-var)))))
700
701 (defmacro input-wrapper/variable-width ((stream bytes eof-error eof-value)
702                                         &body read-forms)
703   (let ((stream-var (gensym))
704         (retry-var (gensym))
705         (element-var (gensym)))
706     `(let ((,stream-var ,stream)
707            (size nil))
708        (if (fd-stream-unread ,stream-var)
709            (prog1
710                (fd-stream-unread ,stream-var)
711              (setf (fd-stream-unread ,stream-var) nil)
712              (setf (fd-stream-listen ,stream-var) nil))
713            (let ((,element-var nil)
714                  (decode-break-reason nil))
715              (do ((,retry-var t))
716                  ((not ,retry-var))
717                (unless
718                    (catch 'eof-input-catcher
719                      (setf decode-break-reason
720                            (block decode-break-reason
721                              (input-at-least ,stream-var 1)
722                              (let* ((byte (sap-ref-8 (fd-stream-ibuf-sap
723                                                       ,stream-var)
724                                                      (fd-stream-ibuf-head
725                                                       ,stream-var))))
726                                (setq size ,bytes)
727                                (input-at-least ,stream-var size)
728                                (setq ,element-var (locally ,@read-forms))
729                                (setq ,retry-var nil))
730                              nil))
731                      (when decode-break-reason
732                        (stream-decoding-error-and-handle stream
733                                                          decode-break-reason))
734                      t)
735                  (let ((octet-count (- (fd-stream-ibuf-tail ,stream-var)
736                                       (fd-stream-ibuf-head ,stream-var))))
737                    (when (or (zerop octet-count)
738                              (and (not ,element-var)
739                                   (not decode-break-reason)
740                                   (stream-decoding-error-and-handle
741                                    stream octet-count)))
742                      (setq ,retry-var nil)))))
743              (cond (,element-var
744                     (incf (fd-stream-ibuf-head ,stream-var) size)
745                     ,element-var)
746                    (t
747                     (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
748
749 ;;; a macro to wrap around all input routines to handle EOF-ERROR noise
750 (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms)
751   (let ((stream-var (gensym))
752         (element-var (gensym)))
753     `(let ((,stream-var ,stream))
754        (if (fd-stream-unread ,stream-var)
755            (prog1
756                (fd-stream-unread ,stream-var)
757              (setf (fd-stream-unread ,stream-var) nil)
758              (setf (fd-stream-listen ,stream-var) nil))
759            (let ((,element-var
760                   (catch 'eof-input-catcher
761                     (input-at-least ,stream-var ,bytes)
762                     (locally ,@read-forms))))
763              (cond (,element-var
764                     (incf (fd-stream-ibuf-head ,stream-var) ,bytes)
765                     ,element-var)
766                    (t
767                     (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
768
769 (defmacro def-input-routine/variable-width (name
770                                             (type external-format size sap head)
771                                             &rest body)
772   `(progn
773      (defun ,name (stream eof-error eof-value)
774        (input-wrapper/variable-width (stream ,size eof-error eof-value)
775          (let ((,sap (fd-stream-ibuf-sap stream))
776                (,head (fd-stream-ibuf-head stream)))
777            ,@body)))
778      (setf *input-routines*
779            (nconc *input-routines*
780                   (list (list ',type ',name 1 ',external-format))))))
781
782 (defmacro def-input-routine (name
783                              (type size sap head)
784                              &rest body)
785   `(progn
786      (defun ,name (stream eof-error eof-value)
787        (input-wrapper (stream ,size eof-error eof-value)
788          (let ((,sap (fd-stream-ibuf-sap stream))
789                (,head (fd-stream-ibuf-head stream)))
790            ,@body)))
791      (setf *input-routines*
792            (nconc *input-routines*
793                   (list (list ',type ',name ',size nil))))))
794
795 ;;; STREAM-IN routine for reading a string char
796 (def-input-routine input-character
797                    (character 1 sap head)
798   (code-char (sap-ref-8 sap head)))
799
800 ;;; STREAM-IN routine for reading an unsigned 8 bit number
801 (def-input-routine input-unsigned-8bit-byte
802                    ((unsigned-byte 8) 1 sap head)
803   (sap-ref-8 sap head))
804
805 ;;; STREAM-IN routine for reading a signed 8 bit number
806 (def-input-routine input-signed-8bit-number
807                    ((signed-byte 8) 1 sap head)
808   (signed-sap-ref-8 sap head))
809
810 ;;; STREAM-IN routine for reading an unsigned 16 bit number
811 (def-input-routine input-unsigned-16bit-byte
812                    ((unsigned-byte 16) 2 sap head)
813   (sap-ref-16 sap head))
814
815 ;;; STREAM-IN routine for reading a signed 16 bit number
816 (def-input-routine input-signed-16bit-byte
817                    ((signed-byte 16) 2 sap head)
818   (signed-sap-ref-16 sap head))
819
820 ;;; STREAM-IN routine for reading a unsigned 32 bit number
821 (def-input-routine input-unsigned-32bit-byte
822                    ((unsigned-byte 32) 4 sap head)
823   (sap-ref-32 sap head))
824
825 ;;; STREAM-IN routine for reading a signed 32 bit number
826 (def-input-routine input-signed-32bit-byte
827                    ((signed-byte 32) 4 sap head)
828   (signed-sap-ref-32 sap head))
829
830
831
832 ;;; Find an input routine to use given the type. Return as multiple
833 ;;; values the routine, the real type transfered, and the number of
834 ;;; bytes per element (and for character types string input routine).
835 (defun pick-input-routine (type &optional external-format)
836   (when (subtypep type 'character)
837     (dolist (entry *external-formats*)
838       (when (member external-format (first entry))
839         (return-from pick-input-routine
840           (values (symbol-function (third entry))
841                   'character
842                   1
843                   (symbol-function (second entry))
844                   (first (first entry)))))))
845   (dolist (entry *input-routines*)
846     (when (and (subtypep type (first entry))
847                (or (not (fourth entry))
848                    (eq external-format (fourth entry))))
849       (return-from pick-input-routine
850         (values (symbol-function (second entry))
851                 (first entry)
852                 (third entry)))))
853   ;; FIXME: let's do it the hard way, then (but ignore things like
854   ;; endianness, efficiency, and the necessary coupling between these
855   ;; and the output routines).  -- CSR, 2004-02-09
856   (loop for i from 40 by 8 to 1024 ; ARB (well, KLUDGE really)
857         if (subtypep type `(unsigned-byte ,i))
858         do (return-from pick-input-routine
859              (values
860               (lambda (stream eof-error eof-value)
861                 (input-wrapper (stream (/ i 8) eof-error eof-value)
862                   (let ((sap (fd-stream-ibuf-sap stream))
863                         (head (fd-stream-ibuf-head stream)))
864                     (loop for j from 0 below (/ i 8)
865                           with result = 0
866                           do (setf result
867                                    (+ (* 256 result)
868                                       (sap-ref-8 sap (+ head j))))
869                           finally (return result)))))
870               `(unsigned-byte ,i)
871               (/ i 8))))
872   (loop for i from 40 by 8 to 1024 ; ARB (well, KLUDGE really)
873         if (subtypep type `(signed-byte ,i))
874         do (return-from pick-input-routine
875              (values
876               (lambda (stream eof-error eof-value)
877                 (input-wrapper (stream (/ i 8) eof-error eof-value)
878                   (let ((sap (fd-stream-ibuf-sap stream))
879                         (head (fd-stream-ibuf-head stream)))
880                     (loop for j from 0 below (/ i 8)
881                           with result = 0
882                           do (setf result
883                                    (+ (* 256 result)
884                                       (sap-ref-8 sap (+ head j))))
885                           finally (return (if (logbitp (1- i) result)
886                                               (dpb result (byte i 0) -1)
887                                               result))))))
888               `(signed-byte ,i)
889               (/ i 8)))))
890
891 ;;; Return a string constructed from SAP, START, and END.
892 (defun string-from-sap (sap start end)
893   (declare (type index start end))
894   (let* ((length (- end start))
895          (string (make-string length)))
896     (copy-ub8-from-system-area sap start
897                                string 0
898                                length)
899     string))
900
901 ;;; the N-BIN method for FD-STREAMs
902 ;;;
903 ;;; Note that this blocks in UNIX-READ. It is generally used where
904 ;;; there is a definite amount of reading to be done, so blocking
905 ;;; isn't too problematical.
906 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p
907                                &aux (total-copied 0))
908   (declare (type fd-stream stream))
909   (declare (type index start requested total-copied))
910   (let ((unread (fd-stream-unread stream)))
911     (when unread
912       ;; AVERs designed to fail when we have more complicated
913       ;; character representations.
914       (aver (typep unread 'base-char))
915       (aver (= (fd-stream-element-size stream) 1))
916       ;; KLUDGE: this is a slightly-unrolled-and-inlined version of
917       ;; %BYTE-BLT
918       (etypecase buffer
919         (system-area-pointer
920          (setf (sap-ref-8 buffer start) (char-code unread)))
921         ((simple-unboxed-array (*))
922          (setf (aref buffer start) unread)))
923       (setf (fd-stream-unread stream) nil)
924       (setf (fd-stream-listen stream) nil)
925       (incf total-copied)))
926   (do ()
927       (nil)
928     (let* ((remaining-request (- requested total-copied))
929            (head (fd-stream-ibuf-head stream))
930            (tail (fd-stream-ibuf-tail stream))
931            (available (- tail head))
932            (n-this-copy (min remaining-request available))
933            (this-start (+ start total-copied))
934            (this-end (+ this-start n-this-copy))
935            (sap (fd-stream-ibuf-sap stream)))
936       (declare (type index remaining-request head tail available))
937       (declare (type index n-this-copy))
938       ;; Copy data from stream buffer into user's buffer. 
939       (%byte-blt sap head buffer this-start this-end)
940       (incf (fd-stream-ibuf-head stream) n-this-copy)
941       (incf total-copied n-this-copy)
942       ;; Maybe we need to refill the stream buffer.
943       (cond (;; If there were enough data in the stream buffer, we're done.
944              (= total-copied requested)
945              (return total-copied))
946             (;; If EOF, we're done in another way.
947              (null (catch 'eof-input-catcher (refill-buffer/fd stream)))
948              (if eof-error-p
949                  (error 'end-of-file :stream stream)
950                  (return total-copied)))
951             ;; Otherwise we refilled the stream buffer, so fall
952             ;; through into another pass of the loop.
953             ))))
954
955 (defun fd-stream-resync (stream)
956   (dolist (entry *external-formats*)
957     (when (member (fd-stream-external-format stream) (first entry))
958       (return-from fd-stream-resync
959         (funcall (symbol-function (eighth entry)) stream)))))
960
961 ;;; FIXME: OAOOM here vrt. *EXTERNAL-FORMAT-FUNCTIONS* in fd-stream.lisp
962 (defmacro define-external-format (external-format size output-restart
963                                   out-expr in-expr)
964   (let* ((name (first external-format))
965          (out-function (symbolicate "OUTPUT-BYTES/" name))
966          (format (format nil "OUTPUT-CHAR-~A-~~A-BUFFERED" (string name)))
967          (in-function (symbolicate "FD-STREAM-READ-N-CHARACTERS/" name))
968          (in-char-function (symbolicate "INPUT-CHAR/" name)))
969     `(progn
970       (defun ,out-function (stream string flush-p start end)
971         (let ((start (or start 0))
972               (end (or end (length string))))
973           (declare (type index start end))
974           (when (and (not (fd-stream-dual-channel-p stream))
975                      (> (fd-stream-ibuf-tail stream)
976                         (fd-stream-ibuf-head stream)))
977             (file-position stream (file-position stream)))
978           (when (< end start)
979             (error ":END before :START!"))
980           (do ()
981               ((= end start))
982             (setf (fd-stream-obuf-tail stream)
983                   (do* ((len (fd-stream-obuf-length stream))
984                         (sap (fd-stream-obuf-sap stream))
985                         (tail (fd-stream-obuf-tail stream)))
986                        ((or (= start end) (< (- len tail) 4)) tail)
987                     ,(if output-restart
988                          `(catch 'output-nothing
989                             (let* ((byte (aref string start))
990                                    (bits (char-code byte)))
991                               ,out-expr
992                               (incf tail ,size)))
993                          `(let* ((byte (aref string start))
994                                   (bits (char-code byte)))
995                              ,out-expr
996                              (incf tail ,size)))
997                     (incf start)))
998             (when (< start end)
999               (flush-output-buffer stream)))
1000           (when flush-p
1001             (flush-output-buffer stream))))
1002       (def-output-routines (,format
1003                             ,size
1004                             ,output-restart
1005                             (:none character)
1006                             (:line character)
1007                             (:full character))
1008           (if (char= byte #\Newline)
1009               (setf (fd-stream-char-pos stream) 0)
1010               (incf (fd-stream-char-pos stream)))
1011         (let ((bits (char-code byte))
1012               (sap (fd-stream-obuf-sap stream))
1013               (tail (fd-stream-obuf-tail stream)))
1014           ,out-expr))
1015       (defun ,in-function (stream buffer start requested eof-error-p
1016                            &aux (total-copied 0))
1017         (declare (type fd-stream stream))
1018         (declare (type index start requested total-copied))
1019         (let ((unread (fd-stream-unread stream)))
1020           (when unread
1021             (setf (aref buffer start) unread)
1022             (setf (fd-stream-unread stream) nil)
1023             (setf (fd-stream-listen stream) nil)
1024             (incf total-copied)))
1025         (do ()
1026             (nil)
1027           (let* ((head (fd-stream-ibuf-head stream))
1028                  (tail (fd-stream-ibuf-tail stream))
1029                  (sap (fd-stream-ibuf-sap stream)))
1030             (declare (type index head tail))
1031             ;; Copy data from stream buffer into user's buffer.
1032             (do ()
1033                 ((or (= tail head) (= requested total-copied)))
1034               (let* ((byte (sap-ref-8 sap head)))
1035                 (when (> ,size (- tail head))
1036                   (return))
1037                 (setf (aref buffer (+ start total-copied)) ,in-expr)
1038                 (incf total-copied)
1039                 (incf head ,size)))
1040             (setf (fd-stream-ibuf-head stream) head)
1041             ;; Maybe we need to refill the stream buffer.
1042             (cond ( ;; If there were enough data in the stream buffer, we're done.
1043                    (= total-copied requested)
1044                    (return total-copied))
1045                   ( ;; If EOF, we're done in another way.
1046                    (null (catch 'eof-input-catcher (refill-buffer/fd stream)))
1047                    (if eof-error-p
1048                        (error 'end-of-file :stream stream)
1049                        (return total-copied)))
1050                   ;; Otherwise we refilled the stream buffer, so fall
1051                   ;; through into another pass of the loop.
1052                   ))))
1053       (def-input-routine ,in-char-function (character ,size sap head)
1054         (let ((byte (sap-ref-8 sap head)))
1055           ,in-expr))
1056       (setf *external-formats*
1057        (cons '(,external-format ,in-function ,in-char-function ,out-function
1058                ,@(mapcar #'(lambda (buffering)
1059                              (intern (format nil format (string buffering))))
1060                          '(:none :line :full)))
1061         *external-formats*)))))
1062
1063 (defmacro define-external-format/variable-width
1064     (external-format output-restart out-size-expr
1065      out-expr in-size-expr in-expr)
1066   (let* ((name (first external-format))
1067          (out-function (symbolicate "OUTPUT-BYTES/" name))
1068          (format (format nil "OUTPUT-CHAR-~A-~~A-BUFFERED" (string name)))
1069          (in-function (symbolicate "FD-STREAM-READ-N-CHARACTERS/" name))
1070          (in-char-function (symbolicate "INPUT-CHAR/" name))
1071          (resync-function (symbolicate "RESYNC/" name)))
1072     `(progn
1073       (defun ,out-function (stream string flush-p start end)
1074         (let ((start (or start 0))
1075               (end (or end (length string))))
1076           (declare (type index start end))
1077           (when (and (not (fd-stream-dual-channel-p stream))
1078                      (> (fd-stream-ibuf-tail stream)
1079                         (fd-stream-ibuf-head stream)))
1080             (file-position stream (file-position stream)))
1081           (when (< end start)
1082             (error ":END before :START!"))
1083           (do ()
1084               ((= end start))
1085             (setf (fd-stream-obuf-tail stream)
1086                   (do* ((len (fd-stream-obuf-length stream))
1087                         (sap (fd-stream-obuf-sap stream))
1088                         (tail (fd-stream-obuf-tail stream)))
1089                        ((or (= start end) (< (- len tail) 4)) tail)
1090                     ,(if output-restart
1091                          `(catch 'output-nothing
1092                             (let* ((byte (aref string start))
1093                                    (bits (char-code byte))
1094                                    (size ,out-size-expr))
1095                               ,out-expr
1096                               (incf tail size)))
1097                          `(let* ((byte (aref string start))
1098                                  (bits (char-code byte))
1099                                  (size ,out-size-expr))
1100                             ,out-expr
1101                             (incf tail size)))
1102                     (incf start)))
1103             (when (< start end)
1104               (flush-output-buffer stream)))
1105           (when flush-p
1106             (flush-output-buffer stream))))
1107       (def-output-routines/variable-width (,format
1108                                            ,out-size-expr
1109                                            ,output-restart
1110                                            ,external-format
1111                                            (:none character)
1112                                            (:line character)
1113                                            (:full character))
1114           (if (char= byte #\Newline)
1115               (setf (fd-stream-char-pos stream) 0)
1116               (incf (fd-stream-char-pos stream)))
1117         (let ((bits (char-code byte))
1118               (sap (fd-stream-obuf-sap stream))
1119               (tail (fd-stream-obuf-tail stream)))
1120           ,out-expr))
1121       (defun ,in-function (stream buffer start requested eof-error-p
1122                            &aux (total-copied 0))
1123         (declare (type fd-stream stream))
1124         (declare (type index start requested total-copied))
1125         (let ((unread (fd-stream-unread stream)))
1126           (when unread
1127             (setf (aref buffer start) unread)
1128             (setf (fd-stream-unread stream) nil)
1129             (setf (fd-stream-listen stream) nil)
1130             (incf total-copied)))
1131         (do ()
1132             (nil)
1133           (let* ((head (fd-stream-ibuf-head stream))
1134                  (tail (fd-stream-ibuf-tail stream))
1135                  (sap (fd-stream-ibuf-sap stream))
1136                  (head-start head)
1137                  (decode-break-reason nil))
1138             (declare (type index head tail))
1139             ;; Copy data from stream buffer into user's buffer.
1140             (do ((size nil nil))
1141                 ((or (= tail head) (= requested total-copied)))
1142               (setf decode-break-reason
1143                     (block decode-break-reason
1144                       (let ((byte (sap-ref-8 sap head)))
1145                         (setq size ,in-size-expr)
1146                         (when (> size (- tail head))
1147                           (return))
1148                         (setf (aref buffer (+ start total-copied)) ,in-expr)
1149                         (incf total-copied)
1150                         (incf head size))
1151                       nil))
1152               (setf (fd-stream-ibuf-head stream) head)
1153               (when (and decode-break-reason
1154                          (= head head-start))
1155                 (when (stream-decoding-error-and-handle
1156                        stream decode-break-reason)
1157                   (if eof-error-p
1158                       (error 'end-of-file :stream stream)
1159                       (return-from ,in-function total-copied)))
1160                 (setf head (fd-stream-ibuf-head stream))
1161                 (setf tail (fd-stream-ibuf-tail stream)))
1162               (when (plusp total-copied)
1163                 (return-from ,in-function total-copied)))
1164             (setf (fd-stream-ibuf-head stream) head)
1165             ;; Maybe we need to refill the stream buffer.
1166             (cond ( ;; If there were enough data in the stream buffer, we're done.
1167                    (= total-copied requested)
1168                    (return total-copied))
1169                   ( ;; If EOF, we're done in another way.
1170                    (or (eq decode-break-reason 'eof)
1171                        (null (catch 'eof-input-catcher 
1172                                (refill-buffer/fd stream))))
1173                    (if eof-error-p
1174                        (error 'end-of-file :stream stream)
1175                        (return total-copied)))
1176                   ;; Otherwise we refilled the stream buffer, so fall
1177                   ;; through into another pass of the loop.
1178                   ))))
1179       (def-input-routine/variable-width ,in-char-function (character
1180                                                            ,external-format
1181                                                            ,in-size-expr
1182                                                            sap head)
1183         (let ((byte (sap-ref-8 sap head)))
1184           ,in-expr))
1185       (defun ,resync-function (stream)
1186         (loop (input-at-least stream 1)
1187               (incf (fd-stream-ibuf-head stream))
1188               (unless (block decode-break-reason
1189                         (let* ((sap (fd-stream-ibuf-sap stream))
1190                                (head (fd-stream-ibuf-head stream))
1191                                (byte (sap-ref-8 sap head))
1192                                (size ,in-size-expr))
1193                           ,in-expr)
1194                         nil)
1195                 (return))))
1196       (setf *external-formats*
1197        (cons '(,external-format ,in-function ,in-char-function ,out-function
1198                ,@(mapcar #'(lambda (buffering)
1199                              (intern (format nil format (string buffering))))
1200                          '(:none :line :full))
1201                ,resync-function)
1202         *external-formats*)))))
1203
1204 (define-external-format (:latin-1 :latin1 :iso-8859-1)
1205     1 t
1206   (if (>= bits 256)
1207       (stream-encoding-error-and-handle stream bits)
1208       (setf (sap-ref-8 sap tail) bits))
1209   (code-char byte))
1210
1211 (define-external-format (:ascii :us-ascii :ansi_x3.4-1968 
1212                          :iso-646 :iso-646-us :|646|)
1213     1 t
1214   (if (>= bits 128)
1215       (stream-encoding-error-and-handle stream bits)
1216       (setf (sap-ref-8 sap tail) bits))
1217   (code-char byte))
1218
1219 (let* ((table (let ((s (make-string 256)))
1220                 (map-into s #'code-char
1221                           '(#x00 #x01 #x02 #x03 #x9c #x09 #x86 #x7f #x97 #x8d #x8e #x0b #x0c #x0d #x0e #x0f
1222                             #x10 #x11 #x12 #x13 #x9d #x85 #x08 #x87 #x18 #x19 #x92 #x8f #x1c #x1d #x1e #x1f
1223                             #x80 #x81 #x82 #x83 #x84 #x0a #x17 #x1b #x88 #x89 #x8a #x8b #x8c #x05 #x06 #x07
1224                             #x90 #x91 #x16 #x93 #x94 #x95 #x96 #x04 #x98 #x99 #x9a #x9b #x14 #x15 #x9e #x1a
1225                             #x20 #xa0 #xe2 #xe4 #xe0 #xe1 #xe3 #xe5 #xe7 #xf1 #xa2 #x2e #x3c #x28 #x2b #x7c
1226                             #x26 #xe9 #xea #xeb #xe8 #xed #xee #xef #xec #xdf #x21 #x24 #x2a #x29 #x3b #xac
1227                             #x2d #x2f #xc2 #xc4 #xc0 #xc1 #xc3 #xc5 #xc7 #xd1 #xa6 #x2c #x25 #x5f #x3e #x3f
1228                             #xf8 #xc9 #xca #xcb #xc8 #xcd #xce #xcf #xcc #x60 #x3a #x23 #x40 #x27 #x3d #x22
1229                             #xd8 #x61 #x62 #x63 #x64 #x65 #x66 #x67 #x68 #x69 #xab #xbb #xf0 #xfd #xfe #xb1
1230                             #xb0 #x6a #x6b #x6c #x6d #x6e #x6f #x70 #x71 #x72 #xaa #xba #xe6 #xb8 #xc6 #xa4
1231                             #xb5 #x7e #x73 #x74 #x75 #x76 #x77 #x78 #x79 #x7a #xa1 #xbf #xd0 #xdd #xde #xae
1232                             #x5e #xa3 #xa5 #xb7 #xa9 #xa7 #xb6 #xbc #xbd #xbe #x5b #x5d #xaf #xa8 #xb4 #xd7
1233                             #x7b #x41 #x42 #x43 #x44 #x45 #x46 #x47 #x48 #x49 #xad #xf4 #xf6 #xf2 #xf3 #xf5
1234                             #x7d #x4a #x4b #x4c #x4d #x4e #x4f #x50 #x51 #x52 #xb9 #xfb #xfc #xf9 #xfa #xff
1235                             #x5c #xf7 #x53 #x54 #x55 #x56 #x57 #x58 #x59 #x5a #xb2 #xd4 #xd6 #xd2 #xd3 #xd5
1236                             #x30 #x31 #x32 #x33 #x34 #x35 #x36 #x37 #x38 #x39 #xb3 #xdb #xdc #xd9 #xda #x9f))
1237                 s))
1238        (reverse-table (let ((rt (make-array 256 :element-type '(unsigned-byte 8) :initial-element 0)))
1239                           (loop for char across table for i from 0
1240                                do (aver (= 0 (aref rt (char-code char))))
1241                                do (setf (aref rt (char-code char)) i))
1242                           rt)))
1243   (define-external-format (:ebcdic-us :ibm-037 :ibm037)
1244       1 t
1245     (if (>= bits 256)
1246         (stream-encoding-error-and-handle stream bits)
1247         (setf (sap-ref-8 sap tail) (aref reverse-table bits)))
1248     (aref table byte)))
1249     
1250
1251 #!+sb-unicode
1252 (let ((latin-9-table (let ((table (make-string 256)))
1253                        (do ((i 0 (1+ i)))
1254                            ((= i 256))
1255                          (setf (aref table i) (code-char i)))
1256                        (setf (aref table #xa4) (code-char #x20ac))
1257                        (setf (aref table #xa6) (code-char #x0160))
1258                        (setf (aref table #xa8) (code-char #x0161))
1259                        (setf (aref table #xb4) (code-char #x017d))
1260                        (setf (aref table #xb8) (code-char #x017e))
1261                        (setf (aref table #xbc) (code-char #x0152))
1262                        (setf (aref table #xbd) (code-char #x0153))
1263                        (setf (aref table #xbe) (code-char #x0178))
1264                        table))
1265       (latin-9-reverse-1 (make-array 16
1266                                      :element-type '(unsigned-byte 21)
1267                                      :initial-contents '(#x0160 #x0161 #x0152 #x0153 0 0 0 0 #x0178 0 0 0 #x20ac #x017d #x017e 0)))
1268       (latin-9-reverse-2 (make-array 16
1269                                      :element-type '(unsigned-byte 8)
1270                                      :initial-contents '(#xa6 #xa8 #xbc #xbd 0 0 0 0 #xbe 0 0 0 #xa4 #xb4 #xb8 0))))
1271   (define-external-format (:latin-9 :latin9 :iso-8859-15)
1272       1 t
1273     (setf (sap-ref-8 sap tail)
1274           (if (< bits 256)
1275               (if (= bits (char-code (aref latin-9-table bits)))
1276                   bits
1277                   (stream-encoding-error-and-handle stream byte))
1278               (if (= (aref latin-9-reverse-1 (logand bits 15)) bits)
1279                   (aref latin-9-reverse-2 (logand bits 15))
1280                   (stream-encoding-error-and-handle stream byte))))
1281     (aref latin-9-table byte)))
1282
1283 (define-external-format/variable-width (:utf-8 :utf8) nil
1284   (let ((bits (char-code byte)))
1285     (cond ((< bits #x80) 1)
1286           ((< bits #x800) 2)
1287           ((< bits #x10000) 3)
1288           (t 4)))
1289   (ecase size
1290     (1 (setf (sap-ref-8 sap tail) bits))
1291     (2 (setf (sap-ref-8 sap tail) (logior #xc0 (ldb (byte 5 6) bits))
1292              (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 0) bits))))
1293     (3 (setf (sap-ref-8 sap tail) (logior #xe0 (ldb (byte 4 12) bits))
1294              (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 6) bits))
1295              (sap-ref-8 sap (+ 2 tail)) (logior #x80 (ldb (byte 6 0) bits))))
1296     (4 (setf (sap-ref-8 sap tail) (logior #xf0 (ldb (byte 3 18) bits))
1297              (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 12) bits))
1298              (sap-ref-8 sap (+ 2 tail)) (logior #x80 (ldb (byte 6 6) bits))
1299              (sap-ref-8 sap (+ 3 tail)) (logior #x80 (ldb (byte 6 0) bits)))))
1300   (cond ((< byte #x80) 1)
1301         ((< byte #xc2) (return-from decode-break-reason 1))
1302         ((< byte #xe0) 2)
1303         ((< byte #xf0) 3)
1304         (t 4))
1305   (code-char (ecase size
1306                (1 byte)
1307                (2 (let ((byte2 (sap-ref-8 sap (1+ head))))
1308                     (unless (<= #x80 byte2 #xbf)
1309                       (return-from decode-break-reason 2))
1310                     (dpb byte (byte 5 6) byte2)))
1311                (3 (let ((byte2 (sap-ref-8 sap (1+ head)))
1312                         (byte3 (sap-ref-8 sap (+ 2 head))))
1313                     (unless (and (<= #x80 byte2 #xbf)
1314                                  (<= #x80 byte3 #xbf))
1315                       (return-from decode-break-reason 3))
1316                     (dpb byte (byte 4 12) (dpb byte2 (byte 6 6) byte3))))
1317                (4 (let ((byte2 (sap-ref-8 sap (1+ head)))
1318                         (byte3 (sap-ref-8 sap (+ 2 head)))
1319                         (byte4 (sap-ref-8 sap (+ 3 head))))
1320                     (unless (and (<= #x80 byte2 #xbf)
1321                                  (<= #x80 byte3 #xbf)
1322                                  (<= #x80 byte4 #xbf))
1323                       (return-from decode-break-reason 4))
1324                     (dpb byte (byte 3 18)
1325                          (dpb byte2 (byte 6 12)
1326                               (dpb byte3 (byte 6 6) byte4))))))))
1327 \f
1328 ;;;; utility functions (misc routines, etc)
1329
1330 ;;; Fill in the various routine slots for the given type. INPUT-P and
1331 ;;; OUTPUT-P indicate what slots to fill. The buffering slot must be
1332 ;;; set prior to calling this routine.
1333 (defun set-fd-stream-routines (fd-stream element-type external-format
1334                                input-p output-p buffer-p)
1335   (let* ((target-type (case element-type
1336                         (unsigned-byte '(unsigned-byte 8))
1337                         (signed-byte '(signed-byte 8))
1338                         (:default 'character)
1339                         (t element-type)))
1340          (character-stream-p (subtypep target-type 'character))
1341          (bivalent-stream-p (eq element-type :default))
1342          normalized-external-format
1343          (bin-routine #'ill-bin)
1344          (bin-type nil)
1345          (bin-size nil)
1346          (cin-routine #'ill-in)
1347          (cin-type nil)
1348          (cin-size nil)
1349          (input-type nil)           ;calculated from bin-type/cin-type
1350          (input-size nil)           ;calculated from bin-size/cin-size
1351          (read-n-characters #'ill-in)
1352          (bout-routine #'ill-bout)
1353          (bout-type nil)
1354          (bout-size nil)
1355          (cout-routine #'ill-out)
1356          (cout-type nil)
1357          (cout-size nil)
1358          (output-type nil)
1359          (output-size nil)
1360          (output-bytes #'ill-bout))
1361
1362     ;; drop buffers when direction changes
1363     (when (and (fd-stream-obuf-sap fd-stream) (not output-p))
1364       (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
1365       (setf (fd-stream-obuf-sap fd-stream) nil))
1366     (when (and (fd-stream-ibuf-sap fd-stream) (not input-p))
1367       (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
1368       (setf (fd-stream-ibuf-sap fd-stream) nil))
1369     (when input-p
1370       (setf (fd-stream-ibuf-sap fd-stream) (next-available-buffer))
1371       (setf (fd-stream-ibuf-length fd-stream) bytes-per-buffer)
1372       (setf (fd-stream-ibuf-tail fd-stream) 0))
1373     (when output-p
1374       (setf (fd-stream-obuf-sap fd-stream) (next-available-buffer))
1375       (setf (fd-stream-obuf-length fd-stream) bytes-per-buffer)
1376       (setf (fd-stream-obuf-tail fd-stream) 0)
1377       (setf (fd-stream-char-pos fd-stream) 0))
1378
1379     (when (and character-stream-p
1380                (eq external-format :default))
1381       (/show0 "/getting default external format")
1382       (setf external-format (default-external-format))
1383       (/show0 "cold-printing defaulted external-format:")
1384       #!+sb-show
1385       (cold-print external-format)
1386       (/show0 "matching to known aliases")
1387       (dolist (entry *external-formats*
1388                      (restart-case
1389                          (error "Invalid external-format ~A" 
1390                                 external-format)
1391                       (use-default ()
1392                         :report "Set external format to LATIN-1"
1393                         (setf external-format :latin-1))))
1394         (/show0 "cold printing known aliases:")
1395         #!+sb-show
1396         (dolist (alias (first entry)) (cold-print alias))
1397         (/show0 "done cold-printing known aliases")
1398         (when (member external-format (first entry))
1399           (/show0 "matched")
1400           (return)))
1401       (/show0 "/default external format ok"))
1402     
1403     (when input-p
1404       (when (or (not character-stream-p) bivalent-stream-p)
1405         (multiple-value-setq (bin-routine bin-type bin-size read-n-characters
1406                                           normalized-external-format)
1407           (pick-input-routine (if bivalent-stream-p '(unsigned-byte 8)
1408                                   target-type)
1409                               external-format))
1410         (unless bin-routine
1411           (error "could not find any input routine for ~S" target-type)))
1412       (when character-stream-p
1413         (multiple-value-setq (cin-routine cin-type cin-size read-n-characters
1414                                           normalized-external-format)
1415           (pick-input-routine target-type external-format))
1416         (unless cin-routine
1417           (error "could not find any input routine for ~S" target-type)))      
1418       (setf (fd-stream-in fd-stream) cin-routine
1419             (fd-stream-bin fd-stream) bin-routine)
1420       ;; character type gets preferential treatment
1421       (setf input-size (or cin-size bin-size))
1422       (setf input-type (or cin-type bin-type))
1423       (when normalized-external-format
1424         (setf (fd-stream-external-format fd-stream)
1425               normalized-external-format))
1426       (when (= (or cin-size 1) (or bin-size 1) 1)
1427         (setf (fd-stream-n-bin fd-stream) ;XXX
1428               (if (and character-stream-p (not bivalent-stream-p))
1429                   read-n-characters
1430                   #'fd-stream-read-n-bytes))
1431         ;; Sometimes turn on fast-read-char/fast-read-byte.  Switch on
1432         ;; for character and (unsigned-byte 8) streams.  In these
1433         ;; cases, fast-read-* will read from the
1434         ;; ansi-stream-(c)in-buffer, saving function calls.
1435         ;; Otherwise, the various data-reading functions in the stream
1436         ;; structure will be called.
1437         (when (and buffer-p
1438                    (not bivalent-stream-p)
1439                    ;; temporary disable on :io streams
1440                    (not output-p))
1441           (cond (character-stream-p 
1442                  (setf (ansi-stream-cin-buffer fd-stream)
1443                        (make-array +ansi-stream-in-buffer-length+
1444                                    :element-type 'character)))
1445                 ((equal target-type '(unsigned-byte 8))
1446                  (setf (ansi-stream-in-buffer fd-stream)
1447                        (make-array +ansi-stream-in-buffer-length+
1448                                    :element-type '(unsigned-byte 8))))))))
1449
1450     (when output-p
1451       (when (or (not character-stream-p) bivalent-stream-p)
1452         (multiple-value-setq (bout-routine bout-type bout-size output-bytes
1453                                            normalized-external-format)
1454           (pick-output-routine (if bivalent-stream-p
1455                                    '(unsigned-byte 8)
1456                                    target-type)
1457                                (fd-stream-buffering fd-stream)
1458                                external-format))
1459         (unless bout-routine
1460           (error "could not find any output routine for ~S buffered ~S"
1461                  (fd-stream-buffering fd-stream)
1462                  target-type)))
1463       (when character-stream-p
1464         (multiple-value-setq (cout-routine cout-type cout-size output-bytes
1465                                            normalized-external-format)
1466           (pick-output-routine target-type
1467                                (fd-stream-buffering fd-stream)
1468                                external-format))
1469         (unless cout-routine
1470           (error "could not find any output routine for ~S buffered ~S"
1471                  (fd-stream-buffering fd-stream)
1472                  target-type)))
1473       (when normalized-external-format
1474         (setf (fd-stream-external-format fd-stream)
1475               normalized-external-format))
1476       (when character-stream-p
1477         (setf (fd-stream-output-bytes fd-stream) output-bytes))
1478       (setf (fd-stream-out fd-stream) cout-routine
1479             (fd-stream-bout fd-stream) bout-routine
1480             (fd-stream-sout fd-stream) (if (eql cout-size 1)
1481                                            #'fd-sout #'ill-out))
1482       (setf output-size (or cout-size bout-size))
1483       (setf output-type (or cout-type bout-type)))
1484
1485     (when (and input-size output-size
1486                (not (eq input-size output-size)))
1487       (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
1488              input-type input-size
1489              output-type output-size))
1490     (setf (fd-stream-element-size fd-stream)
1491           (or input-size output-size))
1492
1493     (setf (fd-stream-element-type fd-stream)
1494           (cond ((equal input-type output-type)
1495                  input-type)
1496                 ((null output-type)
1497                  input-type)
1498                 ((null input-type)
1499                  output-type)
1500                 ((subtypep input-type output-type)
1501                  input-type)
1502                 ((subtypep output-type input-type)
1503                  output-type)
1504                 (t
1505                  (error "Input type (~S) and output type (~S) are unrelated?"
1506                         input-type
1507                         output-type))))))
1508
1509 ;;; Handle miscellaneous operations on FD-STREAM.
1510 (defun fd-stream-misc-routine (fd-stream operation &optional arg1 arg2)
1511   (declare (ignore arg2))
1512   (case operation
1513     (:listen
1514      (or (not (eql (fd-stream-ibuf-head fd-stream)
1515                    (fd-stream-ibuf-tail fd-stream)))
1516          (fd-stream-listen fd-stream)
1517          (setf (fd-stream-listen fd-stream)
1518                (eql (sb!alien:with-alien ((read-fds (sb!alien:struct
1519                                                      sb!unix:fd-set)))
1520                       (sb!unix:fd-zero read-fds)
1521                       (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
1522                       (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
1523                                                 (sb!alien:addr read-fds)
1524                                                 nil nil 0 0))
1525                     1))))
1526     (:unread
1527      (setf (fd-stream-unread fd-stream) arg1)
1528      (setf (fd-stream-listen fd-stream) t))
1529     (:close
1530      (cond (arg1 ; We got us an abort on our hands.
1531             (when (fd-stream-handler fd-stream)
1532               (sb!sys:remove-fd-handler (fd-stream-handler fd-stream))
1533               (setf (fd-stream-handler fd-stream) nil))
1534             ;; We can't do anything unless we know what file were
1535             ;; dealing with, and we don't want to do anything
1536             ;; strange unless we were writing to the file.
1537             (when (and (fd-stream-file fd-stream)
1538                        (fd-stream-obuf-sap fd-stream))
1539               (if (fd-stream-original fd-stream)
1540                   ;; If the original is EQ to file we are appending
1541                   ;; and can just close the file without renaming.
1542                   (unless (eq (fd-stream-original fd-stream)
1543                               (fd-stream-file fd-stream))
1544                     ;; We have a handle on the original, just revert.
1545                     (multiple-value-bind (okay err)
1546                         (sb!unix:unix-rename (fd-stream-original fd-stream)
1547                                              (fd-stream-file fd-stream))
1548                       (unless okay
1549                         (simple-stream-perror
1550                          "couldn't restore ~S to its original contents"
1551                          fd-stream
1552                          err))))
1553                   ;; We can't restore the original, and aren't
1554                   ;; appending, so nuke that puppy.
1555                   ;;
1556                   ;; FIXME: This is currently the fate of superseded
1557                   ;; files, and according to the CLOSE spec this is
1558                   ;; wrong. However, there seems to be no clean way to
1559                   ;; do that that doesn't involve either copying the
1560                   ;; data (bad if the :abort resulted from a full
1561                   ;; disk), or renaming the old file temporarily
1562                   ;; (probably bad because stream opening becomes more
1563                   ;; racy).
1564                   (multiple-value-bind (okay err)
1565                       (sb!unix:unix-unlink (fd-stream-file fd-stream))
1566                     (unless okay
1567                       (error 'simple-file-error
1568                              :pathname (fd-stream-file fd-stream)
1569                              :format-control
1570                              "~@<couldn't remove ~S: ~2I~_~A~:>"
1571                              :format-arguments (list (fd-stream-file fd-stream)
1572                                                      (strerror err))))))))
1573            (t
1574             (fd-stream-misc-routine fd-stream :finish-output)
1575             (when (and (fd-stream-original fd-stream)
1576                        (fd-stream-delete-original fd-stream))
1577               (multiple-value-bind (okay err)
1578                   (sb!unix:unix-unlink (fd-stream-original fd-stream))
1579                 (unless okay
1580                   (error 'simple-file-error
1581                          :pathname (fd-stream-original fd-stream)
1582                          :format-control 
1583                          "~@<couldn't delete ~S during close of ~S: ~
1584                           ~2I~_~A~:>"
1585                          :format-arguments
1586                          (list (fd-stream-original fd-stream)
1587                                fd-stream
1588                                (strerror err))))))))
1589      (when (fboundp 'cancel-finalization)
1590        (cancel-finalization fd-stream))
1591      (sb!unix:unix-close (fd-stream-fd fd-stream))
1592      (when (fd-stream-obuf-sap fd-stream)
1593        (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
1594        (setf (fd-stream-obuf-sap fd-stream) nil))
1595      (when (fd-stream-ibuf-sap fd-stream)
1596        (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
1597        (setf (fd-stream-ibuf-sap fd-stream) nil))
1598      (sb!impl::set-closed-flame fd-stream))
1599     (:clear-input
1600      (setf (fd-stream-unread fd-stream) nil)
1601      (setf (fd-stream-ibuf-head fd-stream) 0)
1602      (setf (fd-stream-ibuf-tail fd-stream) 0)
1603      (catch 'eof-input-catcher
1604        (loop
1605         (let ((count (sb!alien:with-alien ((read-fds (sb!alien:struct
1606                                                       sb!unix:fd-set)))
1607                        (sb!unix:fd-zero read-fds)
1608                        (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
1609                        (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
1610                                                  (sb!alien:addr read-fds)
1611                                                  nil
1612                                                  nil
1613                                                  0
1614                                                  0))))
1615           (cond ((eql count 1)
1616                  (refill-buffer/fd fd-stream)
1617                  (setf (fd-stream-ibuf-head fd-stream) 0)
1618                  (setf (fd-stream-ibuf-tail fd-stream) 0))
1619                 (t
1620                  (return t)))))))
1621     (:force-output
1622      (flush-output-buffer fd-stream))
1623     (:finish-output
1624      (flush-output-buffer fd-stream)
1625      (do ()
1626          ((null (fd-stream-output-later fd-stream)))
1627        (sb!sys:serve-all-events)))
1628     (:element-type
1629      (fd-stream-element-type fd-stream))
1630     (:external-format
1631      (fd-stream-external-format fd-stream))
1632     (:interactive-p
1633      (= 1 (the (member 0 1)
1634             (sb!unix:unix-isatty (fd-stream-fd fd-stream)))))
1635     (:line-length
1636      80)
1637     (:charpos
1638      (fd-stream-char-pos fd-stream))
1639     (:file-length
1640      (unless (fd-stream-file fd-stream)
1641        ;; This is a TYPE-ERROR because ANSI's species FILE-LENGTH
1642        ;; "should signal an error of type TYPE-ERROR if stream is not
1643        ;; a stream associated with a file". Too bad there's no very
1644        ;; appropriate value for the EXPECTED-TYPE slot..
1645        (error 'simple-type-error
1646               :datum fd-stream
1647               :expected-type 'fd-stream
1648               :format-control "~S is not a stream associated with a file."
1649               :format-arguments (list fd-stream)))
1650      (multiple-value-bind (okay dev ino mode nlink uid gid rdev size
1651                            atime mtime ctime blksize blocks)
1652          (sb!unix:unix-fstat (fd-stream-fd fd-stream))
1653        (declare (ignore ino nlink uid gid rdev
1654                         atime mtime ctime blksize blocks))
1655        (unless okay
1656          (simple-stream-perror "failed Unix fstat(2) on ~S" fd-stream dev))
1657        (if (zerop mode)
1658            nil
1659            (truncate size (fd-stream-element-size fd-stream)))))
1660     ;; FIXME: I doubt this is correct in the presence of Unicode,
1661     ;; since fd-stream FILE-POSITION is measured in bytes. 
1662     (:file-string-length
1663      (etypecase arg1
1664        (character 1)
1665        (string (length arg1))))
1666     (:file-position
1667      (fd-stream-file-position fd-stream arg1))))
1668
1669 (defun fd-stream-file-position (stream &optional newpos)
1670   (declare (type fd-stream stream)
1671            (type (or (alien sb!unix:off-t) (member nil :start :end)) newpos))
1672   (if (null newpos)
1673       (sb!sys:without-interrupts
1674         ;; First, find the position of the UNIX file descriptor in the file.
1675         (multiple-value-bind (posn errno)
1676             (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr)
1677           (declare (type (or (alien sb!unix:off-t) null) posn))
1678           (cond ((integerp posn)
1679                  ;; Adjust for buffered output: If there is any output
1680                  ;; buffered, the *real* file position will be larger
1681                  ;; than reported by lseek() because lseek() obviously
1682                  ;; cannot take into account output we have not sent
1683                  ;; yet.
1684                  (dolist (later (fd-stream-output-later stream))
1685                    (incf posn (- (caddr later)
1686                                  (cadr later))))
1687                  (incf posn (fd-stream-obuf-tail stream))
1688                  ;; Adjust for unread input: If there is any input
1689                  ;; read from UNIX but not supplied to the user of the
1690                  ;; stream, the *real* file position will smaller than
1691                  ;; reported, because we want to look like the unread
1692                  ;; stuff is still available.
1693                  (decf posn (- (fd-stream-ibuf-tail stream)
1694                                (fd-stream-ibuf-head stream)))
1695                  (when (fd-stream-unread stream)
1696                    (decf posn))
1697                  ;; Divide bytes by element size.
1698                  (truncate posn (fd-stream-element-size stream)))
1699                 ((eq errno sb!unix:espipe)
1700                  nil)
1701                 (t
1702                  (sb!sys:with-interrupts
1703                    (simple-stream-perror "failure in Unix lseek() on ~S"
1704                                          stream
1705                                          errno))))))
1706       (let ((offset 0) origin)
1707         (declare (type (alien sb!unix:off-t) offset))
1708         ;; Make sure we don't have any output pending, because if we
1709         ;; move the file pointer before writing this stuff, it will be
1710         ;; written in the wrong location.
1711         (flush-output-buffer stream)
1712         (do ()
1713             ((null (fd-stream-output-later stream)))
1714           (sb!sys:serve-all-events))
1715         ;; Clear out any pending input to force the next read to go to
1716         ;; the disk.
1717         (setf (fd-stream-unread stream) nil)
1718         (setf (fd-stream-ibuf-head stream) 0)
1719         (setf (fd-stream-ibuf-tail stream) 0)
1720         ;; Trash cached value for listen, so that we check next time.
1721         (setf (fd-stream-listen stream) nil)
1722         ;; Now move it.
1723         (cond ((eq newpos :start)
1724                (setf offset 0 origin sb!unix:l_set))
1725               ((eq newpos :end)
1726                (setf offset 0 origin sb!unix:l_xtnd))
1727               ((typep newpos '(alien sb!unix:off-t))
1728                (setf offset (* newpos (fd-stream-element-size stream))
1729                      origin sb!unix:l_set))
1730               (t
1731                (error "invalid position given to FILE-POSITION: ~S" newpos)))
1732         (multiple-value-bind (posn errno)
1733             (sb!unix:unix-lseek (fd-stream-fd stream) offset origin)
1734           (cond ((typep posn '(alien sb!unix:off-t))
1735                  t)
1736                 ((eq errno sb!unix:espipe)
1737                  nil)
1738                 (t
1739                  (simple-stream-perror "error in Unix lseek() on ~S"
1740                                        stream
1741                                        errno)))))))
1742 \f
1743 ;;;; creation routines (MAKE-FD-STREAM and OPEN)
1744
1745 ;;; Create a stream for the given Unix file descriptor.
1746 ;;;
1747 ;;; If INPUT is non-NIL, allow input operations. If OUTPUT is non-nil,
1748 ;;; allow output operations. If neither INPUT nor OUTPUT is specified,
1749 ;;; default to allowing input.
1750 ;;;
1751 ;;; ELEMENT-TYPE indicates the element type to use (as for OPEN).
1752 ;;;
1753 ;;; BUFFERING indicates the kind of buffering to use.
1754 ;;;
1755 ;;; TIMEOUT (if true) is the number of seconds to wait for input. If
1756 ;;; NIL (the default), then wait forever. When we time out, we signal
1757 ;;; IO-TIMEOUT.
1758 ;;;
1759 ;;; FILE is the name of the file (will be returned by PATHNAME).
1760 ;;;
1761 ;;; NAME is used to identify the stream when printed.
1762 (defun make-fd-stream (fd
1763                        &key
1764                        (input nil input-p)
1765                        (output nil output-p)
1766                        (element-type 'base-char)
1767                        (buffering :full)
1768                        (external-format :default)
1769                        timeout
1770                        file
1771                        original
1772                        delete-original
1773                        pathname
1774                        input-buffer-p
1775                        dual-channel-p
1776                        (name (if file
1777                                  (format nil "file ~S" file)
1778                                  (format nil "descriptor ~W" fd)))
1779                        auto-close)
1780   (declare (type index fd) (type (or index null) timeout)
1781            (type (member :none :line :full) buffering))
1782   (cond ((not (or input-p output-p))
1783          (setf input t))
1784         ((not (or input output))
1785          (error "File descriptor must be opened either for input or output.")))
1786   (let ((stream (%make-fd-stream :fd fd
1787                                  :name name
1788                                  :file file
1789                                  :original original
1790                                  :delete-original delete-original
1791                                  :pathname pathname
1792                                  :buffering buffering
1793                                  :dual-channel-p dual-channel-p
1794                                  :external-format external-format
1795                                  :timeout timeout)))
1796     (set-fd-stream-routines stream element-type external-format
1797                             input output input-buffer-p)
1798     (when (and auto-close (fboundp 'finalize))
1799       (finalize stream
1800                 (lambda ()
1801                   (sb!unix:unix-close fd)
1802                   #!+sb-show
1803                   (format *terminal-io* "** closed file descriptor ~W **~%"
1804                           fd))))
1805     stream))
1806
1807 ;;; Pick a name to use for the backup file for the :IF-EXISTS
1808 ;;; :RENAME-AND-DELETE and :RENAME options.
1809 (defun pick-backup-name (name)
1810   (declare (type simple-base-string name))
1811   (concatenate 'simple-base-string name ".bak"))
1812
1813 ;;; Ensure that the given arg is one of the given list of valid
1814 ;;; things. Allow the user to fix any problems.
1815 (defun ensure-one-of (item list what)
1816   (unless (member item list)
1817     (error 'simple-type-error
1818            :datum item
1819            :expected-type `(member ,@list)
1820            :format-control "~@<~S is ~_invalid for ~S; ~_need one of~{ ~S~}~:>"
1821            :format-arguments (list item what list))))
1822
1823 ;;; Rename NAMESTRING to ORIGINAL. First, check whether we have write
1824 ;;; access, since we don't want to trash unwritable files even if we
1825 ;;; technically can. We return true if we succeed in renaming.
1826 (defun rename-the-old-one (namestring original)
1827   (unless (sb!unix:unix-access namestring sb!unix:w_ok)
1828     (error "~@<The file ~2I~_~S ~I~_is not writable.~:>" namestring))
1829   (multiple-value-bind (okay err) (sb!unix:unix-rename namestring original)
1830     (if okay
1831         t
1832         (error 'simple-file-error
1833                :pathname namestring
1834                :format-control 
1835                "~@<couldn't rename ~2I~_~S ~I~_to ~2I~_~S: ~4I~_~A~:>"
1836                :format-arguments (list namestring original (strerror err))))))
1837
1838 (defun open (filename
1839              &key
1840              (direction :input)
1841              (element-type 'base-char)
1842              (if-exists nil if-exists-given)
1843              (if-does-not-exist nil if-does-not-exist-given)
1844              (external-format :default)
1845              &aux ; Squelch assignment warning.
1846              (direction direction)
1847              (if-does-not-exist if-does-not-exist)
1848              (if-exists if-exists))
1849   #!+sb-doc
1850   "Return a stream which reads from or writes to FILENAME.
1851   Defined keywords:
1852    :DIRECTION - one of :INPUT, :OUTPUT, :IO, or :PROBE
1853    :ELEMENT-TYPE - the type of object to read or write, default BASE-CHAR
1854    :IF-EXISTS - one of :ERROR, :NEW-VERSION, :RENAME, :RENAME-AND-DELETE,
1855                        :OVERWRITE, :APPEND, :SUPERSEDE or NIL
1856    :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or NIL
1857   See the manual for details."
1858
1859   ;; Calculate useful stuff.
1860   (multiple-value-bind (input output mask)
1861       (case direction
1862         (:input  (values   t nil sb!unix:o_rdonly))
1863         (:output (values nil   t sb!unix:o_wronly))
1864         (:io     (values   t   t sb!unix:o_rdwr))
1865         (:probe  (values   t nil sb!unix:o_rdonly)))
1866     (declare (type index mask))
1867     (let* ((pathname (merge-pathnames filename))
1868            (namestring
1869             (cond ((unix-namestring pathname input))
1870                   ((and input (eq if-does-not-exist :create))
1871                    (unix-namestring pathname nil))
1872                   ((and (eq direction :io) (not if-does-not-exist-given))
1873                    (unix-namestring pathname nil)))))
1874       ;; Process if-exists argument if we are doing any output.
1875       (cond (output
1876              (unless if-exists-given
1877                (setf if-exists
1878                      (if (eq (pathname-version pathname) :newest)
1879                          :new-version
1880                          :error)))
1881              (ensure-one-of if-exists
1882                             '(:error :new-version :rename
1883                                      :rename-and-delete :overwrite
1884                                      :append :supersede nil)
1885                             :if-exists)
1886              (case if-exists
1887                ((:new-version :error nil)
1888                 (setf mask (logior mask sb!unix:o_excl)))
1889                ((:rename :rename-and-delete)
1890                 (setf mask (logior mask sb!unix:o_creat)))
1891                ((:supersede)
1892                 (setf mask (logior mask sb!unix:o_trunc)))
1893                (:append
1894                 (setf mask (logior mask sb!unix:o_append)))))
1895             (t
1896              (setf if-exists :ignore-this-arg)))
1897
1898       (unless if-does-not-exist-given
1899         (setf if-does-not-exist
1900               (cond ((eq direction :input) :error)
1901                     ((and output
1902                           (member if-exists '(:overwrite :append)))
1903                      :error)
1904                     ((eq direction :probe)
1905                      nil)
1906                     (t
1907                      :create))))
1908       (ensure-one-of if-does-not-exist
1909                      '(:error :create nil)
1910                      :if-does-not-exist)
1911       (if (eq if-does-not-exist :create)
1912         (setf mask (logior mask sb!unix:o_creat)))
1913
1914       (let ((original (case if-exists
1915                         ((:rename :rename-and-delete)
1916                          (pick-backup-name namestring))
1917                         ((:append :overwrite)
1918                          ;; KLUDGE: Provent CLOSE from deleting
1919                          ;; appending streams when called with :ABORT T
1920                          namestring)))
1921             (delete-original (eq if-exists :rename-and-delete))
1922             (mode #o666))
1923         (when (and original (not (eq original namestring)))
1924           ;; We are doing a :RENAME or :RENAME-AND-DELETE. Determine
1925           ;; whether the file already exists, make sure the original
1926           ;; file is not a directory, and keep the mode.
1927           (let ((exists
1928                  (and namestring
1929                       (multiple-value-bind (okay err/dev inode orig-mode)
1930                           (sb!unix:unix-stat namestring)
1931                         (declare (ignore inode)
1932                                  (type (or index null) orig-mode))
1933                         (cond
1934                          (okay
1935                           (when (and output (= (logand orig-mode #o170000)
1936                                                #o40000))
1937                             (error 'simple-file-error
1938                                    :pathname namestring
1939                                    :format-control
1940                                    "can't open ~S for output: is a directory"
1941                                    :format-arguments (list namestring)))
1942                           (setf mode (logand orig-mode #o777))
1943                           t)
1944                          ((eql err/dev sb!unix:enoent)
1945                           nil)
1946                          (t
1947                           (simple-file-perror "can't find ~S"
1948                                               namestring
1949                                               err/dev)))))))
1950             (unless (and exists
1951                          (rename-the-old-one namestring original))
1952               (setf original nil)
1953               (setf delete-original nil)
1954               ;; In order to use :SUPERSEDE instead, we have to make
1955               ;; sure SB!UNIX:O_CREAT corresponds to
1956               ;; IF-DOES-NOT-EXIST. SB!UNIX:O_CREAT was set before
1957               ;; because of IF-EXISTS being :RENAME.
1958               (unless (eq if-does-not-exist :create)
1959                 (setf mask
1960                       (logior (logandc2 mask sb!unix:o_creat)
1961                               sb!unix:o_trunc)))
1962               (setf if-exists :supersede))))
1963
1964         ;; Now we can try the actual Unix open(2).
1965         (multiple-value-bind (fd errno)
1966             (if namestring
1967                 (sb!unix:unix-open namestring mask mode)
1968                 (values nil sb!unix:enoent))
1969           (labels ((open-error (format-control &rest format-arguments)
1970                      (error 'simple-file-error
1971                             :pathname pathname
1972                             :format-control format-control
1973                             :format-arguments format-arguments))
1974                    (vanilla-open-error ()
1975                      (simple-file-perror "error opening ~S" pathname errno)))
1976             (cond ((numberp fd)
1977                    (case direction
1978                      ((:input :output :io)
1979                       (make-fd-stream fd
1980                                       :input input
1981                                       :output output
1982                                       :element-type element-type
1983                                       :external-format external-format
1984                                       :file namestring
1985                                       :original original
1986                                       :delete-original delete-original
1987                                       :pathname pathname
1988                                       :dual-channel-p nil
1989                                       :input-buffer-p t
1990                                       :auto-close t))
1991                      (:probe
1992                       (let ((stream
1993                              (%make-fd-stream :name namestring
1994                                               :fd fd
1995                                               :pathname pathname
1996                                               :element-type element-type)))
1997                         (close stream)
1998                         stream))))
1999                   ((eql errno sb!unix:enoent)
2000                    (case if-does-not-exist
2001                      (:error (vanilla-open-error))
2002                      (:create
2003                       (open-error "~@<The path ~2I~_~S ~I~_does not exist.~:>"
2004                                   pathname))
2005                      (t nil)))
2006                   ((and (eql errno sb!unix:eexist) (null if-exists))
2007                    nil)
2008                   (t
2009                    (vanilla-open-error)))))))))
2010 \f
2011 ;;;; initialization
2012
2013 ;;; the stream connected to the controlling terminal, or NIL if there is none
2014 (defvar *tty*)
2015
2016 ;;; the stream connected to the standard input (file descriptor 0)
2017 (defvar *stdin*)
2018
2019 ;;; the stream connected to the standard output (file descriptor 1)
2020 (defvar *stdout*)
2021
2022 ;;; the stream connected to the standard error output (file descriptor 2)
2023 (defvar *stderr*)
2024
2025 ;;; This is called when the cold load is first started up, and may also
2026 ;;; be called in an attempt to recover from nested errors.
2027 (defun stream-cold-init-or-reset ()
2028   (stream-reinit)
2029   (setf *terminal-io* (make-synonym-stream '*tty*))
2030   (setf *standard-output* (make-synonym-stream '*stdout*))
2031   (setf *standard-input* (make-synonym-stream '*stdin*))
2032   (setf *error-output* (make-synonym-stream '*stderr*))
2033   (setf *query-io* (make-synonym-stream '*terminal-io*))
2034   (setf *debug-io* *query-io*)
2035   (setf *trace-output* *standard-output*)
2036   (values))
2037
2038 ;;; This is called whenever a saved core is restarted.
2039 (defun stream-reinit ()
2040   (setf *available-buffers* nil)
2041   (setf *stdin*
2042         (make-fd-stream 0 :name "standard input" :input t :buffering :line))
2043   (setf *stdout*
2044         (make-fd-stream 1 :name "standard output" :output t :buffering :line))
2045   (setf *stderr*
2046         (make-fd-stream 2 :name "standard error" :output t :buffering :line))
2047   (let* ((ttyname #.(coerce "/dev/tty" 'simple-base-string))
2048          (tty (sb!unix:unix-open ttyname sb!unix:o_rdwr #o666)))
2049     (if tty
2050         (setf *tty*
2051               (make-fd-stream tty
2052                               :name "the terminal"
2053                               :input t
2054                               :output t
2055                               :buffering :line
2056                               :auto-close t))
2057         (setf *tty* (make-two-way-stream *stdin* *stdout*))))
2058   (values))
2059 \f
2060 ;;;; miscellany
2061
2062 ;;; the Unix way to beep
2063 (defun beep (stream)
2064   (write-char (code-char bell-char-code) stream)
2065   (finish-output stream))
2066
2067 ;;; This is kind of like FILE-POSITION, but is an internal hack used
2068 ;;; by the filesys stuff to get and set the file name.
2069 ;;;
2070 ;;; FIXME: misleading name, screwy interface
2071 (defun file-name (stream &optional new-name)
2072   (when (typep stream 'fd-stream)
2073       (cond (new-name
2074              (setf (fd-stream-pathname stream) new-name)
2075              (setf (fd-stream-file stream)
2076                    (unix-namestring new-name nil))
2077              t)
2078             (t
2079              (fd-stream-pathname stream)))))