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