Initial revision
[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 (file-comment
15   "$Header$")
16
17 (deftype file-stream () 'fd-stream)
18 \f
19 ;;;; buffer manipulation routines
20
21 (defvar *available-buffers* ()
22   #!+sb-doc
23   "List of available buffers. Each buffer is an sap pointing to
24   bytes-per-buffer of memory.")
25
26 (defconstant bytes-per-buffer (* 4 1024)
27   #!+sb-doc
28   "Number of bytes per buffer.")
29
30 ;;; Return the next available buffer, creating one if necessary.
31 #!-sb-fluid (declaim (inline next-available-buffer))
32 (defun next-available-buffer ()
33   (if *available-buffers*
34       (pop *available-buffers*)
35       (allocate-system-memory bytes-per-buffer)))
36 \f
37 ;;;; the FD-STREAM structure
38
39 (defstruct (fd-stream
40             (:constructor %make-fd-stream)
41             (:include lisp-stream
42                       (misc #'fd-stream-misc-routine)))
43
44   (name nil)                  ; The name of this stream
45   (file nil)                  ; The file this stream is for
46   ;; The backup file namestring for the old file, for :if-exists :rename or
47   ;; :rename-and-delete.
48   (original nil :type (or simple-string null))
49   (delete-original nil)       ; for :if-exists :rename-and-delete
50   ;;; Number of bytes per element.
51   (element-size 1 :type index)
52   (element-type 'base-char)   ; The type of element being transfered.
53   (fd -1 :type fixnum)        ; The file descriptor
54   ;; Controls when the output buffer is flushed.
55   (buffering :full :type (member :full :line :none))
56   ;; Character position if known.
57   (char-pos nil :type (or index null))
58   ;; T if input is waiting on FD. :EOF if we hit EOF.
59   (listen nil :type (member nil t :eof))
60   ;; The input buffer.
61   (unread nil)
62   (ibuf-sap nil :type (or system-area-pointer null))
63   (ibuf-length nil :type (or index null))
64   (ibuf-head 0 :type index)
65   (ibuf-tail 0 :type index)
66
67   ;; The output buffer.
68   (obuf-sap nil :type (or system-area-pointer null))
69   (obuf-length nil :type (or index null))
70   (obuf-tail 0 :type index)
71
72   ;; Output flushed, but not written due to non-blocking io.
73   (output-later nil)
74   (handler nil)
75   ;; Timeout specified for this stream, or NIL if none.
76   (timeout nil :type (or index null))
77   ;; Pathname of the file this stream is opened to (returned by PATHNAME.)
78   (pathname nil :type (or pathname null)))
79 (def!method print-object ((fd-stream fd-stream) stream)
80   (declare (type stream stream))
81   (print-unreadable-object (fd-stream stream :type t :identity t)
82     (format stream "for ~S" (fd-stream-name fd-stream))))
83 \f
84 ;;;; output routines and related noise
85
86 (defvar *output-routines* ()
87   #!+sb-doc
88   "List of all available output routines. Each element is a list of the
89   element-type output, the kind of buffering, the function name, and the number
90   of bytes per element.")
91
92 ;;; Called by the server when we can write to the given file descriptor.
93 ;;; Attempt to write the data again. If it worked, remove the data from the
94 ;;; output-later list. If it didn't work, something is wrong.
95 (defun do-output-later (stream)
96   (let* ((stuff (pop (fd-stream-output-later stream)))
97          (base (car stuff))
98          (start (cadr stuff))
99          (end (caddr stuff))
100          (reuse-sap (cadddr stuff))
101          (length (- end start)))
102     (declare (type index start end length))
103     (multiple-value-bind (count errno)
104         (sb!unix:unix-write (fd-stream-fd stream)
105                             base
106                             start
107                             length)
108       (cond ((not count)
109              (if (= errno sb!unix:ewouldblock)
110                  (error "Write would have blocked, but SERVER told us to go.")
111                  (error "while writing ~S: ~A"
112                         stream
113                         (sb!unix:get-unix-error-msg errno))))
114             ((eql count length) ; Hot damn, it worked.
115              (when reuse-sap
116                (push base *available-buffers*)))
117             ((not (null count)) ; Sorta worked.
118              (push (list base
119                          (the index (+ start count))
120                          end)
121                    (fd-stream-output-later stream))))))
122   (unless (fd-stream-output-later stream)
123     (sb!sys:remove-fd-handler (fd-stream-handler stream))
124     (setf (fd-stream-handler stream) nil)))
125
126 ;;; Arange to output the string when we can write on the file descriptor.
127 (defun output-later (stream base start end reuse-sap)
128   (cond ((null (fd-stream-output-later stream))
129          (setf (fd-stream-output-later stream)
130                (list (list base start end reuse-sap)))
131          (setf (fd-stream-handler stream)
132                (sb!sys:add-fd-handler (fd-stream-fd stream)
133                                       :output
134                                       #'(lambda (fd)
135                                           (declare (ignore fd))
136                                           (do-output-later stream)))))
137         (t
138          (nconc (fd-stream-output-later stream)
139                 (list (list base start end reuse-sap)))))
140   (when reuse-sap
141     (let ((new-buffer (next-available-buffer)))
142       (setf (fd-stream-obuf-sap stream) new-buffer)
143       (setf (fd-stream-obuf-length stream) bytes-per-buffer))))
144
145 ;;; Output the given noise. Check to see whether there are any pending writes.
146 ;;; If so, just queue this one. Otherwise, try to write it. If this would
147 ;;; block, queue it.
148 (defun do-output (stream base start end reuse-sap)
149   (declare (type fd-stream stream)
150            (type (or system-area-pointer (simple-array * (*))) base)
151            (type index start end))
152   (if (not (null (fd-stream-output-later stream))) ; something buffered.
153       (progn
154         (output-later stream base start end reuse-sap)
155         ;; ### check to see whether any of this noise can be output
156         )
157       (let ((length (- end start)))
158         (multiple-value-bind (count errno)
159             (sb!unix:unix-write (fd-stream-fd stream) base start length)
160           (cond ((not count)
161                  (if (= errno sb!unix:ewouldblock)
162                      (output-later stream base start end reuse-sap)
163                      ;; FIXME: This and various other errors in this file
164                      ;; should probably be STREAM-ERROR.
165                      (error "while writing ~S: ~A"
166                             stream
167                             (sb!unix:get-unix-error-msg errno))))
168                 ((not (eql count length))
169                  (output-later stream base (the index (+ start count))
170                                end reuse-sap)))))))
171
172 ;;; Flush any data in the output buffer.
173 (defun flush-output-buffer (stream)
174   (let ((length (fd-stream-obuf-tail stream)))
175     (unless (= length 0)
176       (do-output stream (fd-stream-obuf-sap stream) 0 length t)
177       (setf (fd-stream-obuf-tail stream) 0))))
178
179 ;;; Define output routines that output numbers size bytes long for the
180 ;;; given bufferings. Use body to do the actual output.
181 (defmacro def-output-routines ((name size &rest bufferings) &body body)
182   (declare (optimize (speed 1)))
183   (cons 'progn
184         (mapcar
185             #'(lambda (buffering)
186                 (let ((function
187                        (intern (let ((*print-case* :upcase))
188                                  (format nil name (car buffering))))))
189                   `(progn
190                      (defun ,function (stream byte)
191                        ,(unless (eq (car buffering) :none)
192                           `(when (< (fd-stream-obuf-length stream)
193                                     (+ (fd-stream-obuf-tail stream)
194                                        ,size))
195                              (flush-output-buffer stream)))
196                        ,@body
197                        (incf (fd-stream-obuf-tail stream) ,size)
198                        ,(ecase (car buffering)
199                           (:none
200                            `(flush-output-buffer stream))
201                           (:line
202                            `(when (eq (char-code byte) (char-code #\Newline))
203                               (flush-output-buffer stream)))
204                           (:full
205                            ))
206                        (values))
207                      (setf *output-routines*
208                            (nconc *output-routines*
209                                   ',(mapcar
210                                         #'(lambda (type)
211                                             (list type
212                                                   (car buffering)
213                                                   function
214                                                   size))
215                                       (cdr buffering)))))))
216           bufferings)))
217
218 (def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
219                       1
220                       (:none character)
221                       (:line character)
222                       (:full character))
223   (if (and (base-char-p byte) (char= byte #\Newline))
224       (setf (fd-stream-char-pos stream) 0)
225       (incf (fd-stream-char-pos stream)))
226   (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
227         (char-code byte)))
228
229 (def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
230                       1
231                       (:none (unsigned-byte 8))
232                       (:full (unsigned-byte 8)))
233   (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
234         byte))
235
236 (def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
237                       1
238                       (:none (signed-byte 8))
239                       (:full (signed-byte 8)))
240   (setf (signed-sap-ref-8 (fd-stream-obuf-sap stream)
241                           (fd-stream-obuf-tail stream))
242         byte))
243
244 (def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
245                       2
246                       (:none (unsigned-byte 16))
247                       (:full (unsigned-byte 16)))
248   (setf (sap-ref-16 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
249         byte))
250
251 (def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
252                       2
253                       (:none (signed-byte 16))
254                       (:full (signed-byte 16)))
255   (setf (signed-sap-ref-16 (fd-stream-obuf-sap stream)
256                            (fd-stream-obuf-tail stream))
257         byte))
258
259 (def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
260                       4
261                       (:none (unsigned-byte 32))
262                       (:full (unsigned-byte 32)))
263   (setf (sap-ref-32 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
264         byte))
265
266 (def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
267                       4
268                       (:none (signed-byte 32))
269                       (:full (signed-byte 32)))
270   (setf (signed-sap-ref-32 (fd-stream-obuf-sap stream)
271                            (fd-stream-obuf-tail stream))
272         byte))
273
274 ;;; Does the actual output. If there is space to buffer the string, buffer
275 ;;; it. If the string would normally fit in the buffer, but doesn't because
276 ;;; of other stuff in the buffer, flush the old noise out of the buffer and
277 ;;; put the string in it. Otherwise we have a very long string, so just
278 ;;; send it directly (after flushing the buffer, of course).
279 (defun output-raw-bytes (fd-stream thing &optional start end)
280   #!+sb-doc
281   "Output THING to FD-STREAM. THING can be any kind of vector or a SAP. If
282   THING is a SAP, END must be supplied (as length won't work)."
283   (let ((start (or start 0))
284         (end (or end (length (the (simple-array * (*)) thing)))))
285     (declare (type index start end))
286     (let* ((len (fd-stream-obuf-length fd-stream))
287            (tail (fd-stream-obuf-tail fd-stream))
288            (space (- len tail))
289            (bytes (- end start))
290            (newtail (+ tail bytes)))
291       (cond ((minusp bytes) ; error case
292              (cerror "Just go on as if nothing happened."
293                      "~S called with :END before :START!"
294                      'output-raw-bytes))
295             ((zerop bytes)) ; Easy case
296             ((<= bytes space)
297              (if (system-area-pointer-p thing)
298                  (system-area-copy thing
299                                    (* start sb!vm:byte-bits)
300                                    (fd-stream-obuf-sap fd-stream)
301                                    (* tail sb!vm:byte-bits)
302                                    (* bytes sb!vm:byte-bits))
303                  ;; FIXME: There should be some type checking somewhere to
304                  ;; verify that THING here is a vector, not just <not a SAP>.
305                  (copy-to-system-area thing
306                                       (+ (* start sb!vm:byte-bits)
307                                          (* sb!vm:vector-data-offset
308                                             sb!vm:word-bits))
309                                       (fd-stream-obuf-sap fd-stream)
310                                       (* tail sb!vm:byte-bits)
311                                       (* bytes sb!vm:byte-bits)))
312              (setf (fd-stream-obuf-tail fd-stream) newtail))
313             ((<= bytes len)
314              (flush-output-buffer fd-stream)
315              (if (system-area-pointer-p thing)
316                  (system-area-copy thing
317                                    (* start sb!vm:byte-bits)
318                                    (fd-stream-obuf-sap fd-stream)
319                                    0
320                                    (* bytes sb!vm:byte-bits))
321                  ;; FIXME: There should be some type checking somewhere to
322                  ;; verify that THING here is a vector, not just <not a SAP>.
323                  (copy-to-system-area thing
324                                       (+ (* start sb!vm:byte-bits)
325                                          (* sb!vm:vector-data-offset
326                                             sb!vm:word-bits))
327                                       (fd-stream-obuf-sap fd-stream)
328                                       0
329                                       (* bytes sb!vm:byte-bits)))
330              (setf (fd-stream-obuf-tail fd-stream) bytes))
331             (t
332              (flush-output-buffer fd-stream)
333              (do-output fd-stream thing start end nil))))))
334
335 ;;; Routine to use to output a string. If the stream is unbuffered, slam
336 ;;; the string down the file descriptor, otherwise use OUTPUT-RAW-BYTES to
337 ;;; buffer the string. Update charpos by checking to see where the last newline
338 ;;; was.
339 ;;;
340 ;;; Note: some bozos (the FASL dumper) call write-string with things other
341 ;;; than strings. Therefore, we must make sure we have a string before calling
342 ;;; position on it.
343 ;;; KLUDGE: It would be better to fix the bozos instead of trying to
344 ;;; cover for them here. -- WHN 20000203
345 (defun fd-sout (stream thing start end)
346   (let ((start (or start 0))
347         (end (or end (length (the vector thing)))))
348     (declare (fixnum start end))
349     (if (stringp thing)
350         (let ((last-newline (and (find #\newline (the simple-string thing)
351                                        :start start :end end)
352                                  (position #\newline (the simple-string thing)
353                                            :from-end t
354                                            :start start
355                                            :end end))))
356           (ecase (fd-stream-buffering stream)
357             (:full
358              (output-raw-bytes stream thing start end))
359             (:line
360              (output-raw-bytes stream thing start end)
361              (when last-newline
362                (flush-output-buffer stream)))
363             (:none
364              (do-output stream thing start end nil)))
365           (if last-newline
366               (setf (fd-stream-char-pos stream)
367                     (- end last-newline 1))
368               (incf (fd-stream-char-pos stream)
369                     (- end start))))
370         (ecase (fd-stream-buffering stream)
371           ((:line :full)
372            (output-raw-bytes stream thing start end))
373           (:none
374            (do-output stream thing start end nil))))))
375
376 ;;; Find an output routine to use given the type and buffering. Return as
377 ;;; multiple values the routine, the real type transfered, and the number of
378 ;;; bytes per element.
379 (defun pick-output-routine (type buffering)
380   (dolist (entry *output-routines*)
381     (when (and (subtypep type (car entry))
382                (eq buffering (cadr entry)))
383       (return (values (symbol-function (caddr entry))
384                       (car entry)
385                       (cadddr entry))))))
386 \f
387 ;;;; input routines and related noise
388
389 (defvar *input-routines* ()
390   #!+sb-doc
391   "List of all available input routines. Each element is a list of the
392   element-type input, the function name, and the number of bytes per element.")
393
394 ;;; Fills the input buffer, and returns the first character. Throws to
395 ;;; eof-input-catcher if the eof was reached. Drops into system:server if
396 ;;; necessary.
397 (defun do-input (stream)
398   (let ((fd (fd-stream-fd stream))
399         (ibuf-sap (fd-stream-ibuf-sap stream))
400         (buflen (fd-stream-ibuf-length stream))
401         (head (fd-stream-ibuf-head stream))
402         (tail (fd-stream-ibuf-tail stream)))
403     (declare (type index head tail))
404     (unless (zerop head)
405       (cond ((eql head tail)
406              (setf head 0)
407              (setf tail 0)
408              (setf (fd-stream-ibuf-head stream) 0)
409              (setf (fd-stream-ibuf-tail stream) 0))
410             (t
411              (decf tail head)
412              (system-area-copy ibuf-sap (* head sb!vm:byte-bits)
413                                ibuf-sap 0 (* tail sb!vm:byte-bits))
414              (setf head 0)
415              (setf (fd-stream-ibuf-head stream) 0)
416              (setf (fd-stream-ibuf-tail stream) tail))))
417     (setf (fd-stream-listen stream) nil)
418     (multiple-value-bind (count errno)
419         ;; FIXME: Judging from compiler warnings, this WITH-ALIEN form expands
420         ;; into something which uses the not-yet-defined type
421         ;;   (SB!ALIEN-INTERNALS:ALIEN (* (SB!ALIEN:STRUCT SB!UNIX:FD-SET))).
422         ;; This is probably inefficient and unsafe and generally bad, so
423         ;; try to find some way to make that type known before
424         ;; this is compiled.
425         (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set)))
426           (sb!unix:fd-zero read-fds)
427           (sb!unix:fd-set fd read-fds)
428           (sb!unix:unix-fast-select (1+ fd)
429                                     (sb!alien:addr read-fds)
430                                     nil
431                                     nil
432                                     0
433                                     0))
434       (case count
435         (1)
436         (0
437          (unless #!-mp (sb!sys:wait-until-fd-usable
438                        fd :input (fd-stream-timeout stream))
439                  #!+mp (sb!mp:process-wait-until-fd-usable
440                        fd :input (fd-stream-timeout stream))
441            (error 'io-timeout :stream stream :direction :read)))
442         (t
443          (error "problem checking to see whether ~S is readable: ~A"
444                 stream
445                 (sb!unix:get-unix-error-msg errno)))))
446     (multiple-value-bind (count errno)
447         (sb!unix:unix-read fd
448                            (sb!sys:int-sap (+ (sb!sys:sap-int ibuf-sap) tail))
449                            (- buflen tail))
450       (cond ((null count)
451              (if (eql errno sb!unix:ewouldblock)
452                  (progn
453                    (unless #!-mp (sb!sys:wait-until-fd-usable
454                                  fd :input (fd-stream-timeout stream))
455                            #!+mp (sb!mp:process-wait-until-fd-usable
456                                  fd :input (fd-stream-timeout stream))
457                      (error 'io-timeout :stream stream :direction :read))
458                    (do-input stream))
459                  (error "error reading ~S: ~A"
460                         stream
461                         (sb!unix:get-unix-error-msg errno))))
462             ((zerop count)
463              (setf (fd-stream-listen stream) :eof)
464              (throw 'eof-input-catcher nil))
465             (t
466              (incf (fd-stream-ibuf-tail stream) count))))))
467                         
468 ;;; Makes sure there are at least ``bytes'' number of bytes in the input
469 ;;; buffer. Keeps calling do-input until that condition is met.
470 (defmacro input-at-least (stream bytes)
471   (let ((stream-var (gensym))
472         (bytes-var (gensym)))
473     `(let ((,stream-var ,stream)
474            (,bytes-var ,bytes))
475        (loop
476          (when (>= (- (fd-stream-ibuf-tail ,stream-var)
477                       (fd-stream-ibuf-head ,stream-var))
478                    ,bytes-var)
479            (return))
480          (do-input ,stream-var)))))
481
482 ;;; INPUT-WRAPPER -- intenal
483 ;;;
484 ;;;   Macro to wrap around all input routines to handle eof-error noise.
485 (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms)
486   (let ((stream-var (gensym))
487         (element-var (gensym)))
488     `(let ((,stream-var ,stream))
489        (if (fd-stream-unread ,stream-var)
490            (prog1
491                (fd-stream-unread ,stream-var)
492              (setf (fd-stream-unread ,stream-var) nil)
493              (setf (fd-stream-listen ,stream-var) nil))
494            (let ((,element-var
495                   (catch 'eof-input-catcher
496                     (input-at-least ,stream-var ,bytes)
497                     ,@read-forms)))
498              (cond (,element-var
499                     (incf (fd-stream-ibuf-head ,stream-var) ,bytes)
500                     ,element-var)
501                    (t
502                     (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
503
504 ;;; Defines an input routine.
505 (defmacro def-input-routine (name
506                              (type size sap head)
507                              &rest body)
508   `(progn
509      (defun ,name (stream eof-error eof-value)
510        (input-wrapper (stream ,size eof-error eof-value)
511          (let ((,sap (fd-stream-ibuf-sap stream))
512                (,head (fd-stream-ibuf-head stream)))
513            ,@body)))
514      (setf *input-routines*
515            (nconc *input-routines*
516                   (list (list ',type ',name ',size))))))
517
518 ;;; Routine to use in stream-in slot for reading string chars.
519 (def-input-routine input-character
520                    (character 1 sap head)
521   (code-char (sap-ref-8 sap head)))
522
523 ;;; Routine to read in an unsigned 8 bit number.
524 (def-input-routine input-unsigned-8bit-byte
525                    ((unsigned-byte 8) 1 sap head)
526   (sap-ref-8 sap head))
527
528 ;;; Routine to read in a signed 8 bit number.
529 (def-input-routine input-signed-8bit-number
530                    ((signed-byte 8) 1 sap head)
531   (signed-sap-ref-8 sap head))
532
533 ;;; Routine to read in an unsigned 16 bit number.
534 (def-input-routine input-unsigned-16bit-byte
535                    ((unsigned-byte 16) 2 sap head)
536   (sap-ref-16 sap head))
537
538 ;;; Routine to read in a signed 16 bit number.
539 (def-input-routine input-signed-16bit-byte
540                    ((signed-byte 16) 2 sap head)
541   (signed-sap-ref-16 sap head))
542
543 ;;; Routine to read in a unsigned 32 bit number.
544 (def-input-routine input-unsigned-32bit-byte
545                    ((unsigned-byte 32) 4 sap head)
546   (sap-ref-32 sap head))
547
548 ;;; Routine to read in a signed 32 bit number.
549 (def-input-routine input-signed-32bit-byte
550                    ((signed-byte 32) 4 sap head)
551   (signed-sap-ref-32 sap head))
552
553 ;;; Find an input routine to use given the type. Return as multiple values
554 ;;; the routine, the real type transfered, and the number of bytes per element.
555 (defun pick-input-routine (type)
556   (dolist (entry *input-routines*)
557     (when (subtypep type (car entry))
558       (return (values (symbol-function (cadr entry))
559                       (car entry)
560                       (caddr entry))))))
561
562 ;;; Returns a string constructed from the sap, start, and end.
563 (defun string-from-sap (sap start end)
564   (declare (type index start end))
565   (let* ((length (- end start))
566          (string (make-string length)))
567     (copy-from-system-area sap (* start sb!vm:byte-bits)
568                            string (* sb!vm:vector-data-offset sb!vm:word-bits)
569                            (* length sb!vm:byte-bits))
570     string))
571
572 ;;; old version, not good for implementing READ-SEQUENCE (and just complex)
573 ;;; FIXME: Remove once new FD-STREAM-READ-N-BYTES (below) is stable.
574 #+nil
575 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p)
576   (declare (type stream stream) (type index start requested))
577   (let* ((sap (fd-stream-ibuf-sap stream))
578          (offset start)
579          (head (fd-stream-ibuf-head stream))
580          (tail (fd-stream-ibuf-tail stream))
581          (available (- tail head))
582          (copy (min requested available)))
583     (declare (type index offset head tail available copy))
584     (unless (zerop copy)
585       (if (typep buffer 'system-area-pointer)
586           (system-area-copy sap (* head sb!vm:byte-bits)
587                             buffer (* offset sb!vm:byte-bits)
588                             (* copy sb!vm:byte-bits))
589           (copy-from-system-area sap (* head sb!vm:byte-bits)
590                                  buffer (+ (* offset sb!vm:byte-bits)
591                                            (* sb!vm:vector-data-offset
592                                               sb!vm:word-bits))
593                                  (* copy sb!vm:byte-bits)))
594       (incf (fd-stream-ibuf-head stream) copy))
595     (cond
596      ((or (= copy requested)
597           (and (not eof-error-p) (/= copy 0)))
598       copy)
599      (t
600       (setf (fd-stream-ibuf-head stream) 0)
601       (setf (fd-stream-ibuf-tail stream) 0)
602       (setf (fd-stream-listen stream) nil)
603       (let ((now-needed (- requested copy))
604             (len (fd-stream-ibuf-length stream)))
605         (declare (type index now-needed len))
606         (cond
607          ((> now-needed len)
608           ;; If the desired amount is greater than the stream buffer size, then
609           ;; read directly into the destination, incrementing the start
610           ;; accordingly.  In this case, we never leave anything in the stream
611           ;; buffer.
612           (sb!sys:without-gcing
613             (loop
614               (multiple-value-bind (count err)
615                   (sb!unix:unix-read (fd-stream-fd stream)
616                                      (sap+ (if (typep buffer
617                                                       'system-area-pointer)
618                                                buffer
619                                              (vector-sap buffer))
620                                            (+ offset copy))
621                                      now-needed)
622                 (declare (type (or index null) count))
623                 (unless count
624                   (error "error reading ~S: ~A"
625                          stream
626                          (sb!unix:get-unix-error-msg err)))
627                 (if eof-error-p
628                   (when (zerop count)
629                     (error 'end-of-file :stream stream))
630                   (return (- requested now-needed)))
631                 (decf now-needed count)
632                 (when (zerop now-needed)
633                   (return requested))
634                 (incf offset count)))))
635          (t
636           ;; If we want less than the buffer size, then loop trying to fill the
637           ;; stream buffer and copying what we get into the destination.  When
638           ;; we have enough, we leave what's left in the stream buffer.
639           (loop
640             (multiple-value-bind (count err)
641                 (sb!unix:unix-read (fd-stream-fd stream) sap len)
642               (declare (type (or index null) count))
643               (unless count
644                 (error "error reading ~S: ~A"
645                        stream
646                        (sb!unix:get-unix-error-msg err)))
647               (when (and eof-error-p (zerop count))
648                 (error 'end-of-file :stream stream))
649
650               (let* ((copy (min now-needed count))
651                      (copy-bits (* copy sb!vm:byte-bits))
652                      (buffer-start-bits
653                       (* (+ offset available) sb!vm:byte-bits)))
654                 (declare (type index copy copy-bits buffer-start-bits))
655                 (if (typep buffer 'system-area-pointer)
656                     (system-area-copy sap 0
657                                       buffer buffer-start-bits
658                                       copy-bits)
659                     (copy-from-system-area sap 0 
660                                            buffer (+ buffer-start-bits
661                                                      (* sb!vm:vector-data-offset
662                                                         sb!vm:word-bits))
663                                            copy-bits))
664
665                 (decf now-needed copy)
666                 (when (or (zerop now-needed) (not eof-error-p))
667                   (setf (fd-stream-ibuf-head stream) copy)
668                   (setf (fd-stream-ibuf-tail stream) count)
669                   (return (- requested now-needed)))
670                 (incf offset copy)))))))))))
671
672 ;;; the N-BIN method for FD-STREAMs. This blocks in UNIX-READ. It is generally
673 ;;; used where there is a definite amount of reading to be done, so blocking
674 ;;; isn't too problematical.
675 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p)
676   (declare (type fd-stream stream))
677   (declare (type index start requested))
678   (do ((total-copied 0))
679       (nil)
680     (declare (type index total-copied))
681     (let* ((remaining-request (- requested total-copied))
682            (head (fd-stream-ibuf-head stream))
683            (tail (fd-stream-ibuf-tail stream))
684            (available (- tail head))
685            (this-copy (min remaining-request available))
686            (this-start (+ start total-copied))
687            (sap (fd-stream-ibuf-sap stream)))
688       (declare (type index remaining-request head tail available))
689       (declare (type index this-copy))
690       #+nil
691       (format t
692               "/TOTAL-COPIED=~D HEAD=~D TAIL=~D THIS-COPY=~D~%"
693               total-copied
694               head
695               tail
696               this-copy)
697       ;; Copy data from stream buffer into user's buffer. 
698       (if (typep buffer 'system-area-pointer)
699           (system-area-copy sap (* head sb!vm:byte-bits)
700                             buffer (* this-start sb!vm:byte-bits)
701                             (* this-copy sb!vm:byte-bits))
702           (copy-from-system-area sap (* head sb!vm:byte-bits)
703                                  buffer (+ (* this-start sb!vm:byte-bits)
704                                            (* sb!vm:vector-data-offset
705                                               sb!vm:word-bits))
706                                  (* this-copy sb!vm:byte-bits)))
707       (incf (fd-stream-ibuf-head stream) this-copy)
708       (incf total-copied this-copy)
709       ;; Maybe we need to refill the stream buffer.
710       (cond (;; If there were enough data in the stream buffer, we're done.
711              (= total-copied requested)
712              #+nil
713              (format t "/enough data~%")
714              (return total-copied))
715             (;; If EOF, we're done in another way.
716              (zerop (refill-fd-stream-buffer stream))
717              #+nil
718              (format t "/end of file~%")
719              (if eof-error-p
720                  (error 'end-of-file :stream stream)
721                  (return total-copied)))
722             ;; Otherwise we refilled the stream buffer, so fall through into
723             ;; another pass of the loop.
724             ))))
725
726 ;;; Try to refill the stream buffer. Return the number of bytes read. (For EOF,
727 ;;; the return value will be zero, otherwise positive.)
728 (defun refill-fd-stream-buffer (stream)
729   ;; We don't have any logic to preserve leftover bytes in the buffer,
730   ;; so we should only be called when the buffer is empty.
731   (assert (= (fd-stream-ibuf-head stream) (fd-stream-ibuf-tail stream)))
732   (multiple-value-bind (count err)
733       (sb!unix:unix-read (fd-stream-fd stream)
734                          (fd-stream-ibuf-sap stream)
735                          (fd-stream-ibuf-length stream))
736     (declare (type (or index null) count))
737     (when (null count)
738       (error "error reading ~S: ~A"
739              stream
740              (sb!unix:get-unix-error-msg err)))
741     (setf (fd-stream-listen stream) nil
742           (fd-stream-ibuf-head stream) 0
743           (fd-stream-ibuf-tail stream) count)
744 ;    (format t "~%buffer=~%--~%")
745 ;    (dotimes (i count)
746 ;      (write-char (code-char (sap-ref-8 (fd-stream-ibuf-sap stream) i))))
747 ;    (format t "~%--~%")
748     #+nil
749     (format t "/REFILL-FD-STREAM-BUFFER = ~D~%" count)
750     count))
751 \f
752 ;;;; utility functions (misc routines, etc)
753
754 ;;; Fill in the various routine slots for the given type. Input-p and
755 ;;; output-p indicate what slots to fill. The buffering slot must be set prior
756 ;;; to calling this routine.
757 (defun set-routines (stream type input-p output-p buffer-p)
758   (let ((target-type (case type
759                        ((:default unsigned-byte)
760                         '(unsigned-byte 8))
761                        (signed-byte
762                         '(signed-byte 8))
763                        (t
764                         type)))
765         (input-type nil)
766         (output-type nil)
767         (input-size nil)
768         (output-size nil))
769
770     (when (fd-stream-obuf-sap stream)
771       (push (fd-stream-obuf-sap stream) *available-buffers*)
772       (setf (fd-stream-obuf-sap stream) nil))
773     (when (fd-stream-ibuf-sap stream)
774       (push (fd-stream-ibuf-sap stream) *available-buffers*)
775       (setf (fd-stream-ibuf-sap stream) nil))
776
777     (when input-p
778       (multiple-value-bind (routine type size)
779           (pick-input-routine target-type)
780         (unless routine
781           (error "could not find any input routine for ~S" target-type))
782         (setf (fd-stream-ibuf-sap stream) (next-available-buffer))
783         (setf (fd-stream-ibuf-length stream) bytes-per-buffer)
784         (setf (fd-stream-ibuf-tail stream) 0)
785         (if (subtypep type 'character)
786             (setf (fd-stream-in stream) routine
787                   (fd-stream-bin stream) #'ill-bin)
788             (setf (fd-stream-in stream) #'ill-in
789                   (fd-stream-bin stream) routine))
790         (when (eql size 1)
791           (setf (fd-stream-n-bin stream) #'fd-stream-read-n-bytes)
792           (when buffer-p
793             (setf (lisp-stream-in-buffer stream)
794                   (make-array in-buffer-length
795                               :element-type '(unsigned-byte 8)))))
796         (setf input-size size)
797         (setf input-type type)))
798
799     (when output-p
800       (multiple-value-bind (routine type size)
801           (pick-output-routine target-type (fd-stream-buffering stream))
802         (unless routine
803           (error "could not find any output routine for ~S buffered ~S"
804                  (fd-stream-buffering stream)
805                  target-type))
806         (setf (fd-stream-obuf-sap stream) (next-available-buffer))
807         (setf (fd-stream-obuf-length stream) bytes-per-buffer)
808         (setf (fd-stream-obuf-tail stream) 0)
809         (if (subtypep type 'character)
810           (setf (fd-stream-out stream) routine
811                 (fd-stream-bout stream) #'ill-bout)
812           (setf (fd-stream-out stream)
813                 (or (if (eql size 1)
814                       (pick-output-routine 'base-char
815                                            (fd-stream-buffering stream)))
816                     #'ill-out)
817                 (fd-stream-bout stream) routine))
818         (setf (fd-stream-sout stream)
819               (if (eql size 1) #'fd-sout #'ill-out))
820         (setf (fd-stream-char-pos stream) 0)
821         (setf output-size size)
822         (setf output-type type)))
823
824     (when (and input-size output-size
825                (not (eq input-size output-size)))
826       (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
827              input-type input-size
828              output-type output-size))
829     (setf (fd-stream-element-size stream)
830           (or input-size output-size))
831
832     (setf (fd-stream-element-type stream)
833           (cond ((equal input-type output-type)
834                  input-type)
835                 ((null output-type)
836                  input-type)
837                 ((null input-type)
838                  output-type)
839                 ((subtypep input-type output-type)
840                  input-type)
841                 ((subtypep output-type input-type)
842                  output-type)
843                 (t
844                  (error "Input type (~S) and output type (~S) are unrelated?"
845                         input-type
846                         output-type))))))
847
848 ;;; Handle miscellaneous operations on fd-stream.
849 (defun fd-stream-misc-routine (stream operation &optional arg1 arg2)
850   (declare (ignore arg2))
851   ;; FIXME: Declare TYPE FD-STREAM STREAM?
852   (case operation
853     (:listen
854      (or (not (eql (fd-stream-ibuf-head stream)
855                    (fd-stream-ibuf-tail stream)))
856          (fd-stream-listen stream)
857          (setf (fd-stream-listen stream)
858                (eql (sb!alien:with-alien ((read-fds (sb!alien:struct
859                                                      sb!unix:fd-set)))
860                       (sb!unix:fd-zero read-fds)
861                       (sb!unix:fd-set (fd-stream-fd stream) read-fds)
862                       (sb!unix:unix-fast-select (1+ (fd-stream-fd stream))
863                                                 (sb!alien:addr read-fds)
864                                                 nil nil 0 0))
865                     1))))
866     (:unread
867      (setf (fd-stream-unread stream) arg1)
868      (setf (fd-stream-listen stream) t))
869     (:close
870      (cond (arg1
871             ;; We got us an abort on our hands.
872             (when (fd-stream-handler stream)
873                   (sb!sys:remove-fd-handler (fd-stream-handler stream))
874                   (setf (fd-stream-handler stream) nil))
875             (when (and (fd-stream-file stream)
876                        (fd-stream-obuf-sap stream))
877               ;; Can't do anything unless we know what file were dealing with,
878               ;; and we don't want to do anything strange unless we were
879               ;; writing to the file.
880               (if (fd-stream-original stream)
881                   ;; We have a handle on the original, just revert.
882                   (multiple-value-bind (okay err)
883                       (sb!unix:unix-rename (fd-stream-original stream)
884                                            (fd-stream-file stream))
885                     (unless okay
886                       (cerror "Go on as if nothing bad happened."
887                         "could not restore ~S to its original contents: ~A"
888                               (fd-stream-file stream)
889                               (sb!unix:get-unix-error-msg err))))
890                   ;; Can't restore the orignal, so nuke that puppy.
891                   (multiple-value-bind (okay err)
892                       (sb!unix:unix-unlink (fd-stream-file stream))
893                     (unless okay
894                       (cerror "Go on as if nothing bad happened."
895                               "Could not remove ~S: ~A"
896                               (fd-stream-file stream)
897                               (sb!unix:get-unix-error-msg err)))))))
898            (t
899             (fd-stream-misc-routine stream :finish-output)
900             (when (and (fd-stream-original stream)
901                        (fd-stream-delete-original stream))
902               (multiple-value-bind (okay err)
903                   (sb!unix:unix-unlink (fd-stream-original stream))
904                 (unless okay
905                   (cerror "Go on as if nothing bad happened."
906                           "could not delete ~S during close of ~S: ~A"
907                           (fd-stream-original stream)
908                           stream
909                           (sb!unix:get-unix-error-msg err)))))))
910      (when (fboundp 'cancel-finalization)
911        (cancel-finalization stream))
912      (sb!unix:unix-close (fd-stream-fd stream))
913      (when (fd-stream-obuf-sap stream)
914        (push (fd-stream-obuf-sap stream) *available-buffers*)
915        (setf (fd-stream-obuf-sap stream) nil))
916      (when (fd-stream-ibuf-sap stream)
917        (push (fd-stream-ibuf-sap stream) *available-buffers*)
918        (setf (fd-stream-ibuf-sap stream) nil))
919      (sb!impl::set-closed-flame stream))
920     (:clear-input
921      (setf (fd-stream-unread stream) nil)
922      (setf (fd-stream-ibuf-head stream) 0)
923      (setf (fd-stream-ibuf-tail stream) 0)
924      (catch 'eof-input-catcher
925        (loop
926         (let ((count (sb!alien:with-alien ((read-fds (sb!alien:struct
927                                                       sb!unix:fd-set)))
928                        (sb!unix:fd-zero read-fds)
929                        (sb!unix:fd-set (fd-stream-fd stream) read-fds)
930                        (sb!unix:unix-fast-select (1+ (fd-stream-fd stream))
931                                               (sb!alien:addr read-fds)
932                                               nil
933                                               nil
934                                               0
935                                               0))))
936           (cond ((eql count 1)
937                  (do-input stream)
938                  (setf (fd-stream-ibuf-head stream) 0)
939                  (setf (fd-stream-ibuf-tail stream) 0))
940                 (t
941                  (return t)))))))
942     (:force-output
943      (flush-output-buffer stream))
944     (:finish-output
945      (flush-output-buffer stream)
946      (do ()
947          ((null (fd-stream-output-later stream)))
948        (sb!sys:serve-all-events)))
949     (:element-type
950      (fd-stream-element-type stream))
951     (:interactive-p
952      (sb!unix:unix-isatty (fd-stream-fd stream)))
953     (:line-length
954      80)
955     (:charpos
956      (fd-stream-char-pos stream))
957     (:file-length
958      (multiple-value-bind (okay dev ino mode nlink uid gid rdev size
959                            atime mtime ctime blksize blocks)
960          (sb!unix:unix-fstat (fd-stream-fd stream))
961        (declare (ignore ino nlink uid gid rdev
962                         atime mtime ctime blksize blocks))
963        (unless okay
964          (error "error fstat'ing ~S: ~A"
965                 stream
966                 (sb!unix:get-unix-error-msg dev)))
967        (if (zerop (the index mode))
968            nil
969            ;; FIXME: It's not safe to assume that SIZE is an INDEX, there
970            ;; are files bigger than that.
971            (truncate (the index size) (fd-stream-element-size stream)))))
972     (:file-position
973      (fd-stream-file-position stream arg1))))
974
975 (defun fd-stream-file-position (stream &optional newpos)
976   (declare (type fd-stream stream)
977            (type (or index (member nil :start :end)) newpos))
978   (if (null newpos)
979       (sb!sys:without-interrupts
980         ;; First, find the position of the UNIX file descriptor in the
981         ;; file.
982         (multiple-value-bind (posn errno)
983             (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr)
984           (declare (type (or index null) posn))
985           (cond ((fixnump posn)
986                  ;; Adjust for buffered output:
987                  ;;  If there is any output buffered, the *real* file position
988                  ;; will be larger than reported by lseek because lseek
989                  ;; obviously cannot take into account output we have not
990                  ;; sent yet.
991                  (dolist (later (fd-stream-output-later stream))
992                    (incf posn (- (the index (caddr later))
993                                  (the index (cadr later)))))
994                  (incf posn (fd-stream-obuf-tail stream))
995                  ;; Adjust for unread input:
996                  ;;  If there is any input read from UNIX but not supplied to
997                  ;; the user of the stream, the *real* file position will
998                  ;; smaller than reported, because we want to look like the
999                  ;; unread stuff is still available.
1000                  (decf posn (- (fd-stream-ibuf-tail stream)
1001                                (fd-stream-ibuf-head stream)))
1002                  (when (fd-stream-unread stream)
1003                    (decf posn))
1004                  ;; Divide bytes by element size.
1005                  (truncate posn (fd-stream-element-size stream)))
1006                 ((eq errno sb!unix:espipe)
1007                  nil)
1008                 (t
1009                  (sb!sys:with-interrupts
1010                    (error "error LSEEK'ing ~S: ~A"
1011                           stream
1012                           (sb!unix:get-unix-error-msg errno)))))))
1013       (let ((offset 0) origin)
1014         (declare (type index offset))
1015         ;; Make sure we don't have any output pending, because if we move the
1016         ;; file pointer before writing this stuff, it will be written in the
1017         ;; wrong location.
1018         (flush-output-buffer stream)
1019         (do ()
1020             ((null (fd-stream-output-later stream)))
1021           (sb!sys:serve-all-events))
1022         ;; Clear out any pending input to force the next read to go to the
1023         ;; disk.
1024         (setf (fd-stream-unread stream) nil)
1025         (setf (fd-stream-ibuf-head stream) 0)
1026         (setf (fd-stream-ibuf-tail stream) 0)
1027         ;; Trash cached value for listen, so that we check next time.
1028         (setf (fd-stream-listen stream) nil)
1029         ;; Now move it.
1030         (cond ((eq newpos :start)
1031                (setf offset 0 origin sb!unix:l_set))
1032               ((eq newpos :end)
1033                (setf offset 0 origin sb!unix:l_xtnd))
1034               ((typep newpos 'index)
1035                (setf offset (* newpos (fd-stream-element-size stream))
1036                      origin sb!unix:l_set))
1037               (t
1038                (error "invalid position given to file-position: ~S" newpos)))
1039         (multiple-value-bind (posn errno)
1040             (sb!unix:unix-lseek (fd-stream-fd stream) offset origin)
1041           (cond ((typep posn 'fixnum)
1042                  t)
1043                 ((eq errno sb!unix:espipe)
1044                  nil)
1045                 (t
1046                  (error "error lseek'ing ~S: ~A"
1047                         stream
1048                         (sb!unix:get-unix-error-msg errno))))))))
1049 \f
1050 ;;;; creation routines (MAKE-FD-STREAM and OPEN)
1051
1052 ;;; Returns a FD-STREAM on the given file.
1053 (defun make-fd-stream (fd
1054                        &key
1055                        (input nil input-p)
1056                        (output nil output-p)
1057                        (element-type 'base-char)
1058                        (buffering :full)
1059                        timeout
1060                        file
1061                        original
1062                        delete-original
1063                        pathname
1064                        input-buffer-p
1065                        (name (if file
1066                                  (format nil "file ~S" file)
1067                                  (format nil "descriptor ~D" fd)))
1068                        auto-close)
1069   (declare (type index fd) (type (or index null) timeout)
1070            (type (member :none :line :full) buffering))
1071   #!+sb-doc
1072   "Create a stream for the given unix file descriptor.
1073   If input is non-nil, allow input operations.
1074   If output is non-nil, allow output operations.
1075   If neither input nor output are specified, default to allowing input.
1076   Element-type indicates the element type to use (as for open).
1077   Buffering indicates the kind of buffering to use.
1078   Timeout (if true) is the number of seconds to wait for input. If NIL (the
1079     default), then wait forever. When we time out, we signal IO-TIMEOUT.
1080   File is the name of the file (will be returned by PATHNAME).
1081   Name is used to identify the stream when printed."
1082   (cond ((not (or input-p output-p))
1083          (setf input t))
1084         ((not (or input output))
1085          (error "File descriptor must be opened either for input or output.")))
1086   (let ((stream (%make-fd-stream :fd fd
1087                                  :name name
1088                                  :file file
1089                                  :original original
1090                                  :delete-original delete-original
1091                                  :pathname pathname
1092                                  :buffering buffering
1093                                  :timeout timeout)))
1094     (set-routines stream element-type input output input-buffer-p)
1095     (when (and auto-close (fboundp 'finalize))
1096       (finalize stream
1097                 (lambda ()
1098                   (sb!unix:unix-close fd)
1099                   #!+sb-show
1100                   (format *terminal-io* "** closed file descriptor ~D **~%"
1101                           fd))))
1102     stream))
1103
1104 ;;; Pick a name to use for the backup file.
1105 (defvar *backup-extension* ".BAK"
1106   #!+sb-doc
1107   "This is a string that OPEN tacks on the end of a file namestring to produce
1108    a name for the :if-exists :rename-and-delete and :rename options. Also,
1109    this can be a function that takes a namestring and returns a complete
1110    namestring.")
1111 (defun pick-backup-name (name)
1112   (declare (type simple-string name))
1113   (let ((ext *backup-extension*))
1114     (etypecase ext
1115       (simple-string (concatenate 'simple-string name ext))
1116       (function (funcall ext name)))))
1117
1118 ;;; Ensure that the given arg is one of the given list of valid things.
1119 ;;; Allow the user to fix any problems.
1120 ;;; FIXME: Why let the user fix any problems?
1121 (defun ensure-one-of (item list what)
1122   (unless (member item list)
1123     (loop
1124       (cerror "Enter new value for ~*~S"
1125               "~S is invalid for ~S. Must be one of~{ ~S~}"
1126               item
1127               what
1128               list)
1129       (format (the stream *query-io*) "Enter new value for ~S: " what)
1130       (force-output *query-io*)
1131       (setf item (read *query-io*))
1132       (when (member item list)
1133         (return))))
1134   item)
1135
1136 ;;; Rename Namestring to Original. First, check whether we have write access,
1137 ;;; since we don't want to trash unwritable files even if we technically can.
1138 ;;; We return true if we succeed in renaming.
1139 (defun do-old-rename (namestring original)
1140   (unless (sb!unix:unix-access namestring sb!unix:w_ok)
1141     (cerror "Try to rename it anyway."
1142             "File ~S is not writable."
1143             namestring))
1144   (multiple-value-bind (okay err) (sb!unix:unix-rename namestring original)
1145     (cond (okay t)
1146           (t
1147            (cerror "Use :SUPERSEDE instead."
1148                    "Could not rename ~S to ~S: ~A."
1149                    namestring
1150                    original
1151                    (sb!unix:get-unix-error-msg err))
1152            nil))))
1153
1154 (defun open (filename
1155              &key
1156              (direction :input)
1157              (element-type 'base-char)
1158              (if-exists nil if-exists-given)
1159              (if-does-not-exist nil if-does-not-exist-given)
1160              (external-format :default)
1161              &aux ; Squelch assignment warning.
1162              (direction direction)
1163              (if-does-not-exist if-does-not-exist)
1164              (if-exists if-exists))
1165   #!+sb-doc
1166   "Return a stream which reads from or writes to Filename.
1167   Defined keywords:
1168    :direction - one of :input, :output, :io, or :probe
1169    :element-type - Type of object to read or write, default BASE-CHAR
1170    :if-exists - one of :error, :new-version, :rename, :rename-and-delete,
1171                        :overwrite, :append, :supersede or nil
1172    :if-does-not-exist - one of :error, :create or nil
1173   See the manual for details."
1174
1175   (unless (eq external-format :default)
1176     (error 'simple-error
1177            :format-control
1178            "Any external format other than :DEFAULT isn't recognized."))
1179
1180   ;; First, make sure that DIRECTION is valid. Allow it to be changed
1181   ;; if not.
1182   ;;
1183   ;; FIXME: Why allow it to be changed if not?
1184   (setf direction
1185         (ensure-one-of direction
1186                        '(:input :output :io :probe)
1187                        :direction))
1188
1189   ;; Calculate useful stuff.
1190   (multiple-value-bind (input output mask)
1191       (case direction
1192         (:input  (values   t nil sb!unix:o_rdonly))
1193         (:output (values nil   t sb!unix:o_wronly))
1194         (:io     (values   t   t sb!unix:o_rdwr))
1195         (:probe  (values   t nil sb!unix:o_rdonly)))
1196     (declare (type index mask))
1197     (let* ((pathname (pathname filename))
1198            (namestring
1199             (cond ((unix-namestring pathname input))
1200                   ((and input (eq if-does-not-exist :create))
1201                    (unix-namestring pathname nil)))))
1202       ;; Process if-exists argument if we are doing any output.
1203       (cond (output
1204              (unless if-exists-given
1205                (setf if-exists
1206                      (if (eq (pathname-version pathname) :newest)
1207                          :new-version
1208                          :error)))
1209              (setf if-exists ; FIXME: should just die, not allow resetting
1210                    (ensure-one-of if-exists
1211                                   '(:error :new-version :rename
1212                                     :rename-and-delete :overwrite
1213                                     :append :supersede nil)
1214                                   :if-exists))
1215              (case if-exists
1216                ((:error nil)
1217                 (setf mask (logior mask sb!unix:o_excl)))
1218                ((:rename :rename-and-delete)
1219                 (setf mask (logior mask sb!unix:o_creat)))
1220                ((:new-version :supersede)
1221                 (setf mask (logior mask sb!unix:o_trunc)))
1222                (:append
1223                 (setf mask (logior mask sb!unix:o_append)))))
1224             (t
1225              (setf if-exists :ignore-this-arg)))
1226
1227       (unless if-does-not-exist-given
1228         (setf if-does-not-exist
1229               (cond ((eq direction :input) :error)
1230                     ((and output
1231                           (member if-exists '(:overwrite :append)))
1232                      :error)
1233                     ((eq direction :probe)
1234                      nil)
1235                     (t
1236                      :create))))
1237       (setf if-does-not-exist ; FIXME: should just die, not allow resetting
1238             (ensure-one-of if-does-not-exist
1239                            '(:error :create nil)
1240                            :if-does-not-exist))
1241       (if (eq if-does-not-exist :create)
1242         (setf mask (logior mask sb!unix:o_creat)))
1243
1244       (let ((original (if (member if-exists
1245                                   '(:rename :rename-and-delete))
1246                           (pick-backup-name namestring)))
1247             (delete-original (eq if-exists :rename-and-delete))
1248             (mode #o666))
1249         (when original
1250           ;; We are doing a :RENAME or :RENAME-AND-DELETE.
1251           ;; Determine whether the file already exists, make sure the original
1252           ;; file is not a directory, and keep the mode.
1253           (let ((exists
1254                  (and namestring
1255                       (multiple-value-bind (okay err/dev inode orig-mode)
1256                           (sb!unix:unix-stat namestring)
1257                         (declare (ignore inode)
1258                                  (type (or index null) orig-mode))
1259                         (cond
1260                          (okay
1261                           (when (and output (= (logand orig-mode #o170000)
1262                                                #o40000))
1263                             (error "cannot open ~S for output: is a directory"
1264                                    namestring))
1265                           (setf mode (logand orig-mode #o777))
1266                           t)
1267                          ((eql err/dev sb!unix:enoent)
1268                           nil)
1269                          (t
1270                           (error "cannot find ~S: ~A"
1271                                  namestring
1272                                  (sb!unix:get-unix-error-msg err/dev))))))))
1273             (unless (and exists
1274                          (do-old-rename namestring original))
1275               (setf original nil)
1276               (setf delete-original nil)
1277               ;; In order to use :SUPERSEDE instead, we have to make sure
1278               ;; SB!UNIX:O_CREAT corresponds to IF-DOES-NOT-EXIST.
1279               ;; SB!UNIX:O_CREAT was set before because of IF-EXISTS being
1280               ;; :RENAME.
1281               (unless (eq if-does-not-exist :create)
1282                 (setf mask
1283                       (logior (logandc2 mask sb!unix:o_creat)
1284                               sb!unix:o_trunc)))
1285               (setf if-exists :supersede))))
1286         
1287         ;; Okay, now we can try the actual open.
1288         (loop
1289           (multiple-value-bind (fd errno)
1290               (if namestring
1291                   (sb!unix:unix-open namestring mask mode)
1292                   (values nil sb!unix:enoent))
1293             (cond ((numberp fd)
1294                    (return
1295                     (case direction
1296                       ((:input :output :io)
1297                        (make-fd-stream fd
1298                                        :input input
1299                                        :output output
1300                                        :element-type element-type
1301                                        :file namestring
1302                                        :original original
1303                                        :delete-original delete-original
1304                                        :pathname pathname
1305                                        :input-buffer-p t
1306                                        :auto-close t))
1307                       (:probe
1308                        (let ((stream
1309                               (%make-fd-stream :name namestring :fd fd
1310                                                :pathname pathname
1311                                                :element-type element-type)))
1312                          (close stream)
1313                          stream)))))
1314                   ((eql errno sb!unix:enoent)
1315                    (case if-does-not-exist
1316                      (:error
1317                       (cerror "Return NIL."
1318                               'simple-file-error
1319                               :pathname pathname
1320                               :format-control "error opening ~S: ~A"
1321                               :format-arguments
1322                               (list pathname
1323                                     (sb!unix:get-unix-error-msg errno))))
1324                      (:create
1325                       (cerror "Return NIL."
1326                               'simple-error
1327                               :format-control
1328                               "error creating ~S: Path does not exist."
1329                               :format-arguments
1330                               (list pathname))))
1331                    (return nil))
1332                   ((eql errno sb!unix:eexist)
1333                    (unless (eq nil if-exists)
1334                      (cerror "Return NIL."
1335                              'simple-file-error
1336                              :pathname pathname
1337                              :format-control "error opening ~S: ~A"
1338                              :format-arguments
1339                              (list pathname
1340                                    (sb!unix:get-unix-error-msg errno))))
1341                    (return nil))
1342                   ((eql errno sb!unix:eacces)
1343                    (cerror "Try again."
1344                            "error opening ~S: ~A"
1345                            pathname
1346                            (sb!unix:get-unix-error-msg errno)))
1347                   (t
1348                    (cerror "Return NIL."
1349                            "error opening ~S: ~A"
1350                            pathname
1351                            (sb!unix:get-unix-error-msg errno))
1352                    (return nil)))))))))
1353 \f
1354 ;;;; initialization
1355
1356 (defvar *tty* nil
1357   #!+sb-doc
1358   "The stream connected to the controlling terminal or NIL if there is none.")
1359 (defvar *stdin* nil
1360   #!+sb-doc
1361   "The stream connected to the standard input (file descriptor 0).")
1362 (defvar *stdout* nil
1363   #!+sb-doc
1364   "The stream connected to the standard output (file descriptor 1).")
1365 (defvar *stderr* nil
1366   #!+sb-doc
1367   "The stream connected to the standard error output (file descriptor 2).")
1368
1369 ;;; This is called when the cold load is first started up, and may also
1370 ;;; be called in an attempt to recover from nested errors.
1371 (defun stream-cold-init-or-reset ()
1372   (stream-reinit)
1373   (setf *terminal-io* (make-synonym-stream '*tty*))
1374   (setf *standard-output* (make-synonym-stream '*stdout*))
1375   (setf *standard-input*
1376         (#!-high-security
1377          ;; FIXME: Why is *STANDARD-INPUT* a TWO-WAY-STREAM? ANSI says it's
1378          ;; an input stream.
1379          make-two-way-stream
1380          #!+high-security
1381          %make-two-way-stream (make-synonym-stream '*stdin*)
1382                              *standard-output*))
1383   (setf *error-output* (make-synonym-stream '*stderr*))
1384   (setf *query-io* (make-synonym-stream '*terminal-io*))
1385   (setf *debug-io* *query-io*)
1386   (setf *trace-output* *standard-output*)
1387   nil)
1388
1389 ;;; This is called whenever a saved core is restarted.
1390 (defun stream-reinit ()
1391   (setf *available-buffers* nil)
1392   (setf *stdin*
1393         (make-fd-stream 0 :name "standard input" :input t :buffering :line))
1394   (setf *stdout*
1395         (make-fd-stream 1 :name "standard output" :output t :buffering :line))
1396   (setf *stderr*
1397         (make-fd-stream 2 :name "standard error" :output t :buffering :line))
1398   (let ((tty (sb!unix:unix-open "/dev/tty" sb!unix:o_rdwr #o666)))
1399     (if tty
1400         (setf *tty*
1401               (make-fd-stream tty
1402                               :name "the terminal"
1403                               :input t
1404                               :output t
1405                               :buffering :line
1406                               :auto-close t))
1407         (setf *tty* (make-two-way-stream *stdin* *stdout*))))
1408   nil)
1409 \f
1410 ;;;; beeping
1411
1412 (defun default-beep-function (stream)
1413   (write-char (code-char bell-char-code) stream)
1414   (finish-output stream))
1415
1416 (defvar *beep-function* #'default-beep-function
1417   #!+sb-doc
1418   "This is called in BEEP to feep the user. It takes a stream.")
1419
1420 (defun beep (&optional (stream *terminal-io*))
1421   (funcall *beep-function* stream))
1422 \f
1423 ;;; Kind of like FILE-POSITION, but is an internal hack used by the filesys
1424 ;;; stuff to get and set the file name.
1425 (defun file-name (stream &optional new-name)
1426   (when (typep stream 'fd-stream)
1427       (cond (new-name
1428              (setf (fd-stream-pathname stream) new-name)
1429              (setf (fd-stream-file stream)
1430                    (unix-namestring new-name nil))
1431              t)
1432             (t
1433              (fd-stream-pathname stream)))))
1434 \f
1435 ;;;; international character support (which is trivial for our simple
1436 ;;;; character sets)
1437
1438 ;;;; (Those who do Lisp only in English might not remember that ANSI requires
1439 ;;;; these functions to be exported from package COMMON-LISP.)
1440
1441 (defun file-string-length (stream object)
1442   (declare (type (or string character) object) (type file-stream stream))
1443   #!+sb-doc
1444   "Return the delta in STREAM's FILE-POSITION that would be caused by writing
1445    Object to Stream. Non-trivial only in implementations that support
1446    international character sets."
1447   (declare (ignore stream))
1448   (etypecase object
1449     (character 1)
1450     (string (length object))))
1451
1452 (defun stream-external-format (stream)
1453   (declare (type file-stream stream) (ignore stream))
1454   #!+sb-doc
1455   "Return :DEFAULT."
1456   :default)