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