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