1 ;;;; streams for UNIX file descriptors
3 ;;;; This software is part of the SBCL system. See the README file for
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.
12 (in-package "SB!IMPL")
14 ;;; FIXME: Wouldn't it be clearer to just have the structure
15 ;;; definition be DEFSTRUCT FILE-STREAM (instead of DEFSTRUCT
16 ;;; FD-STREAM)? That way we'd have TYPE-OF and PRINT-OBJECT refer to
17 ;;; these objects as FILE-STREAMs (the ANSI name) instead of the
18 ;;; internal implementation name FD-STREAM, and there might be other
20 (deftype file-stream () 'fd-stream)
22 ;;;; buffer manipulation routines
24 ;;; FIXME: Is it really good to maintain this pool separate from the
25 ;;; GC and the C malloc logic?
26 (defvar *available-buffers* ()
28 "List of available buffers. Each buffer is an sap pointing to
29 bytes-per-buffer of memory.")
31 (defconstant bytes-per-buffer (* 4 1024)
33 "Number of bytes per buffer.")
35 ;;; Return the next available buffer, creating one if necessary.
36 #!-sb-fluid (declaim (inline next-available-buffer))
37 (defun next-available-buffer ()
38 (if *available-buffers*
39 (pop *available-buffers*)
40 (allocate-system-memory bytes-per-buffer)))
42 ;;;; the FD-STREAM structure
45 (:constructor %make-fd-stream)
47 (misc #'fd-stream-misc-routine))
50 ;; the name of this stream
52 ;; the file this stream is for
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
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))
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)
79 (obuf-sap nil :type (or system-area-pointer null))
80 (obuf-length nil :type (or index null))
81 (obuf-tail 0 :type index)
83 ;; output flushed, but not written due to non-blocking io?
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 (def!method print-object ((fd-stream fd-stream) stream)
91 (declare (type stream stream))
92 (print-unreadable-object (fd-stream stream :type t :identity t)
93 (format stream "for ~S" (fd-stream-name fd-stream))))
95 ;;;; output routines and related noise
97 (defvar *output-routines* ()
99 "List of all available output routines. Each element is a list of the
100 element-type output, the kind of buffering, the function name, and the number
101 of bytes per element.")
103 ;;; common idioms for reporting low-level stream and file problems
104 (defun simple-stream-perror (note-format stream errno)
105 (error 'simple-stream-error
107 :format-control "~@<~?: ~2I~_~A~:>"
108 :format-arguments (list note-format (list stream) (strerror errno))))
109 (defun simple-file-perror (note-format pathname errno)
110 (error 'simple-file-error
112 :format-control "~@<~?: ~2I~_~A~:>"
114 (list note-format (list pathname) (strerror errno))))
116 ;;; This is called by the server when we can write to the given file
117 ;;; descriptor. Attempt to write the data again. If it worked, remove
118 ;;; the data from the OUTPUT-LATER list. If it didn't work, something
120 (defun frob-output-later (stream)
121 (let* ((stuff (pop (fd-stream-output-later stream)))
125 (reuse-sap (cadddr stuff))
126 (length (- end start)))
127 (declare (type index start end length))
128 (multiple-value-bind (count errno)
129 (sb!unix:unix-write (fd-stream-fd stream)
134 (if (= errno sb!unix:ewouldblock)
135 (error "Write would have blocked, but SERVER told us to go.")
136 (simple-stream-perror "couldn't write to ~S" stream errno)))
137 ((eql count length) ; Hot damn, it worked.
139 (push base *available-buffers*)))
140 ((not (null count)) ; sorta worked..
142 (the index (+ start count))
144 (fd-stream-output-later stream))))))
145 (unless (fd-stream-output-later stream)
146 (sb!sys:remove-fd-handler (fd-stream-handler stream))
147 (setf (fd-stream-handler stream) nil)))
149 ;;; Arange to output the string when we can write on the file descriptor.
150 (defun output-later (stream base start end reuse-sap)
151 (cond ((null (fd-stream-output-later stream))
152 (setf (fd-stream-output-later stream)
153 (list (list base start end reuse-sap)))
154 (setf (fd-stream-handler stream)
155 (sb!sys:add-fd-handler (fd-stream-fd stream)
158 (declare (ignore fd))
159 (frob-output-later stream)))))
161 (nconc (fd-stream-output-later stream)
162 (list (list base start end reuse-sap)))))
164 (let ((new-buffer (next-available-buffer)))
165 (setf (fd-stream-obuf-sap stream) new-buffer)
166 (setf (fd-stream-obuf-length stream) bytes-per-buffer))))
168 ;;; Output the given noise. Check to see whether there are any pending
169 ;;; writes. If so, just queue this one. Otherwise, try to write it. If
170 ;;; this would block, queue it.
171 (defun frob-output (stream base start end reuse-sap)
172 (declare (type fd-stream stream)
173 (type (or system-area-pointer (simple-array * (*))) base)
174 (type index start end))
175 (if (not (null (fd-stream-output-later stream))) ; something buffered.
177 (output-later stream base start end reuse-sap)
178 ;; ### check to see whether any of this noise can be output
180 (let ((length (- end start)))
181 (multiple-value-bind (count errno)
182 (sb!unix:unix-write (fd-stream-fd stream) base start length)
184 (if (= errno sb!unix:ewouldblock)
185 (output-later stream base start end reuse-sap)
186 (simple-stream-perror "couldn't write to ~S"
189 ((not (eql count length))
190 (output-later stream base (the index (+ start count))
193 ;;; Flush any data in the output buffer.
194 (defun flush-output-buffer (stream)
195 (let ((length (fd-stream-obuf-tail stream)))
197 (frob-output stream (fd-stream-obuf-sap stream) 0 length t)
198 (setf (fd-stream-obuf-tail stream) 0))))
200 ;;; Define output routines that output numbers SIZE bytes long for the
201 ;;; given bufferings. Use BODY to do the actual output.
202 (defmacro def-output-routines ((name-fmt size &rest bufferings) &body body)
203 (declare (optimize (speed 1)))
208 (intern (let ((*print-case* :upcase))
209 (format nil name-fmt (car buffering))))))
211 (defun ,function (stream byte)
212 ,(unless (eq (car buffering) :none)
213 `(when (< (fd-stream-obuf-length stream)
214 (+ (fd-stream-obuf-tail stream)
216 (flush-output-buffer stream)))
218 (incf (fd-stream-obuf-tail stream) ,size)
219 ,(ecase (car buffering)
221 `(flush-output-buffer stream))
223 `(when (eq (char-code byte) (char-code #\Newline))
224 (flush-output-buffer stream)))
228 (setf *output-routines*
229 (nconc *output-routines*
236 (cdr buffering)))))))
239 (def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
244 (if (and (base-char-p byte) (char= byte #\Newline))
245 (setf (fd-stream-char-pos stream) 0)
246 (incf (fd-stream-char-pos stream)))
247 (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
250 (def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
252 (:none (unsigned-byte 8))
253 (:full (unsigned-byte 8)))
254 (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
257 (def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
259 (:none (signed-byte 8))
260 (:full (signed-byte 8)))
261 (setf (signed-sap-ref-8 (fd-stream-obuf-sap stream)
262 (fd-stream-obuf-tail stream))
265 (def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
267 (:none (unsigned-byte 16))
268 (:full (unsigned-byte 16)))
269 (setf (sap-ref-16 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
272 (def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
274 (:none (signed-byte 16))
275 (:full (signed-byte 16)))
276 (setf (signed-sap-ref-16 (fd-stream-obuf-sap stream)
277 (fd-stream-obuf-tail stream))
280 (def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
282 (:none (unsigned-byte 32))
283 (:full (unsigned-byte 32)))
284 (setf (sap-ref-32 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
287 (def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
289 (:none (signed-byte 32))
290 (:full (signed-byte 32)))
291 (setf (signed-sap-ref-32 (fd-stream-obuf-sap stream)
292 (fd-stream-obuf-tail stream))
295 ;;; Do the actual output. If there is space to buffer the string,
296 ;;; buffer it. If the string would normally fit in the buffer, but
297 ;;; doesn't because of other stuff in the buffer, flush the old noise
298 ;;; out of the buffer and put the string in it. Otherwise we have a
299 ;;; very long string, so just send it directly (after flushing the
300 ;;; buffer, of course).
301 (defun output-raw-bytes (fd-stream thing &optional start end)
303 "Output THING to FD-STREAM. THING can be any kind of vector or a SAP. If
304 THING is a SAP, END must be supplied (as length won't work)."
305 (let ((start (or start 0))
306 (end (or end (length (the (simple-array * (*)) thing)))))
307 (declare (type index start end))
308 (let* ((len (fd-stream-obuf-length fd-stream))
309 (tail (fd-stream-obuf-tail fd-stream))
311 (bytes (- end start))
312 (newtail (+ tail bytes)))
313 (cond ((minusp bytes) ; error case
314 (error ":END before :START!"))
315 ((zerop bytes)) ; easy case
317 (if (system-area-pointer-p thing)
318 (system-area-copy thing
319 (* start sb!vm:n-byte-bits)
320 (fd-stream-obuf-sap fd-stream)
321 (* tail sb!vm:n-byte-bits)
322 (* bytes sb!vm:n-byte-bits))
323 ;; FIXME: There should be some type checking somewhere to
324 ;; verify that THING here is a vector, not just <not a SAP>.
325 (copy-to-system-area thing
326 (+ (* start sb!vm:n-byte-bits)
327 (* sb!vm:vector-data-offset
329 (fd-stream-obuf-sap fd-stream)
330 (* tail sb!vm:n-byte-bits)
331 (* bytes sb!vm:n-byte-bits)))
332 (setf (fd-stream-obuf-tail fd-stream) newtail))
334 (flush-output-buffer fd-stream)
335 (if (system-area-pointer-p thing)
336 (system-area-copy thing
337 (* start sb!vm:n-byte-bits)
338 (fd-stream-obuf-sap fd-stream)
340 (* bytes sb!vm:n-byte-bits))
341 ;; FIXME: There should be some type checking somewhere to
342 ;; verify that THING here is a vector, not just <not a SAP>.
343 (copy-to-system-area thing
344 (+ (* start sb!vm:n-byte-bits)
345 (* sb!vm:vector-data-offset
347 (fd-stream-obuf-sap fd-stream)
349 (* bytes sb!vm:n-byte-bits)))
350 (setf (fd-stream-obuf-tail fd-stream) bytes))
352 (flush-output-buffer fd-stream)
353 (frob-output fd-stream thing start end nil))))))
355 ;;; the routine to use to output a string. If the stream is
356 ;;; unbuffered, slam the string down the file descriptor, otherwise
357 ;;; use OUTPUT-RAW-BYTES to buffer the string. Update charpos by
358 ;;; checking to see where the last newline was.
360 ;;; Note: some bozos (the FASL dumper) call write-string with things
361 ;;; other than strings. Therefore, we must make sure we have a string
362 ;;; before calling POSITION on it.
363 ;;; KLUDGE: It would be better to fix the bozos instead of trying to
364 ;;; cover for them here. -- WHN 20000203
365 (defun fd-sout (stream thing start end)
366 (let ((start (or start 0))
367 (end (or end (length (the vector thing)))))
368 (declare (fixnum start end))
370 (let ((last-newline (and (find #\newline (the simple-string thing)
371 :start start :end end)
372 (position #\newline (the simple-string thing)
376 (ecase (fd-stream-buffering stream)
378 (output-raw-bytes stream thing start end))
380 (output-raw-bytes stream thing start end)
382 (flush-output-buffer stream)))
384 (frob-output stream thing start end nil)))
386 (setf (fd-stream-char-pos stream)
387 (- end last-newline 1))
388 (incf (fd-stream-char-pos stream)
390 (ecase (fd-stream-buffering stream)
392 (output-raw-bytes stream thing start end))
394 (frob-output stream thing start end nil))))))
396 ;;; Find an output routine to use given the type and buffering. Return
397 ;;; as multiple values the routine, the real type transfered, and the
398 ;;; number of bytes per element.
399 (defun pick-output-routine (type buffering)
400 (dolist (entry *output-routines*)
401 (when (and (subtypep type (car entry))
402 (eq buffering (cadr entry)))
403 (return (values (symbol-function (caddr entry))
407 ;;;; input routines and related noise
409 ;;; a list of all available input routines. Each element is a list of
410 ;;; the element-type input, the function name, and the number of bytes
412 (defvar *input-routines* ())
414 ;;; Fill the input buffer, and return the first character. Throw to
415 ;;; EOF-INPUT-CATCHER if the eof was reached. Drop into SYSTEM:SERVER
417 (defun frob-input (stream)
418 (let ((fd (fd-stream-fd stream))
419 (ibuf-sap (fd-stream-ibuf-sap stream))
420 (buflen (fd-stream-ibuf-length stream))
421 (head (fd-stream-ibuf-head stream))
422 (tail (fd-stream-ibuf-tail stream)))
423 (declare (type index head tail))
425 (cond ((eql head tail)
428 (setf (fd-stream-ibuf-head stream) 0)
429 (setf (fd-stream-ibuf-tail stream) 0))
432 (system-area-copy ibuf-sap (* head sb!vm:n-byte-bits)
433 ibuf-sap 0 (* tail sb!vm:n-byte-bits))
435 (setf (fd-stream-ibuf-head stream) 0)
436 (setf (fd-stream-ibuf-tail stream) tail))))
437 (setf (fd-stream-listen stream) nil)
438 (multiple-value-bind (count errno)
439 ;; FIXME: Judging from compiler warnings, this WITH-ALIEN form expands
440 ;; into something which uses the not-yet-defined type
441 ;; (SB!ALIEN-INTERNALS:ALIEN (* (SB!ALIEN:STRUCT SB!UNIX:FD-SET))).
442 ;; This is probably inefficient and unsafe and generally bad, so
443 ;; try to find some way to make that type known before
445 (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set)))
446 (sb!unix:fd-zero read-fds)
447 (sb!unix:fd-set fd read-fds)
448 (sb!unix:unix-fast-select (1+ fd)
449 (sb!alien:addr read-fds)
457 (unless #!-mp (sb!sys:wait-until-fd-usable
458 fd :input (fd-stream-timeout stream))
459 #!+mp (sb!mp:process-wait-until-fd-usable
460 fd :input (fd-stream-timeout stream))
461 (error 'io-timeout :stream stream :direction :read)))
463 (simple-stream-perror "couldn't check whether ~S is readable"
466 (multiple-value-bind (count errno)
467 (sb!unix:unix-read fd
468 (sb!sys:int-sap (+ (sb!sys:sap-int ibuf-sap) tail))
471 (if (eql errno sb!unix:ewouldblock)
473 (unless #!-mp (sb!sys:wait-until-fd-usable
474 fd :input (fd-stream-timeout stream))
475 #!+mp (sb!mp:process-wait-until-fd-usable
476 fd :input (fd-stream-timeout stream))
477 (error 'io-timeout :stream stream :direction :read))
479 (simple-stream-perror "couldn't read from ~S" stream errno)))
481 (setf (fd-stream-listen stream) :eof)
482 (/show0 "THROWing EOF-INPUT-CATCHER")
483 (throw 'eof-input-catcher nil))
485 (incf (fd-stream-ibuf-tail stream) count))))))
487 ;;; Make sure there are at least BYTES number of bytes in the input
488 ;;; buffer. Keep calling FROB-INPUT until that condition is met.
489 (defmacro input-at-least (stream bytes)
490 (let ((stream-var (gensym))
491 (bytes-var (gensym)))
492 `(let ((,stream-var ,stream)
495 (when (>= (- (fd-stream-ibuf-tail ,stream-var)
496 (fd-stream-ibuf-head ,stream-var))
499 (frob-input ,stream-var)))))
501 ;;; a macro to wrap around all input routines to handle EOF-ERROR noise
502 (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms)
503 (let ((stream-var (gensym))
504 (element-var (gensym)))
505 `(let ((,stream-var ,stream))
506 (if (fd-stream-unread ,stream-var)
508 (fd-stream-unread ,stream-var)
509 (setf (fd-stream-unread ,stream-var) nil)
510 (setf (fd-stream-listen ,stream-var) nil))
512 (catch 'eof-input-catcher
513 (input-at-least ,stream-var ,bytes)
516 (incf (fd-stream-ibuf-head ,stream-var) ,bytes)
519 (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
521 (defmacro def-input-routine (name
525 (defun ,name (stream eof-error eof-value)
526 (input-wrapper (stream ,size eof-error eof-value)
527 (let ((,sap (fd-stream-ibuf-sap stream))
528 (,head (fd-stream-ibuf-head stream)))
530 (setf *input-routines*
531 (nconc *input-routines*
532 (list (list ',type ',name ',size))))))
534 ;;; STREAM-IN routine for reading a string char
535 (def-input-routine input-character
536 (character 1 sap head)
537 (code-char (sap-ref-8 sap head)))
539 ;;; STREAM-IN routine for reading an unsigned 8 bit number
540 (def-input-routine input-unsigned-8bit-byte
541 ((unsigned-byte 8) 1 sap head)
542 (sap-ref-8 sap head))
544 ;;; STREAM-IN routine for reading a signed 8 bit number
545 (def-input-routine input-signed-8bit-number
546 ((signed-byte 8) 1 sap head)
547 (signed-sap-ref-8 sap head))
549 ;;; STREAM-IN routine for reading an unsigned 16 bit number
550 (def-input-routine input-unsigned-16bit-byte
551 ((unsigned-byte 16) 2 sap head)
552 (sap-ref-16 sap head))
554 ;;; STREAM-IN routine for reading a signed 16 bit number
555 (def-input-routine input-signed-16bit-byte
556 ((signed-byte 16) 2 sap head)
557 (signed-sap-ref-16 sap head))
559 ;;; STREAM-IN routine for reading a unsigned 32 bit number
560 (def-input-routine input-unsigned-32bit-byte
561 ((unsigned-byte 32) 4 sap head)
562 (sap-ref-32 sap head))
564 ;;; STREAM-IN routine for reading a signed 32 bit number
565 (def-input-routine input-signed-32bit-byte
566 ((signed-byte 32) 4 sap head)
567 (signed-sap-ref-32 sap head))
569 ;;; Find an input routine to use given the type. Return as multiple
570 ;;; values the routine, the real type transfered, and the number of
571 ;;; bytes per element.
572 (defun pick-input-routine (type)
573 (dolist (entry *input-routines*)
574 (when (subtypep type (car entry))
575 (return (values (symbol-function (cadr entry))
579 ;;; Return a string constructed from SAP, START, and END.
580 (defun string-from-sap (sap start end)
581 (declare (type index start end))
582 (let* ((length (- end start))
583 (string (make-string length)))
584 (copy-from-system-area sap (* start sb!vm:n-byte-bits)
585 string (* sb!vm:vector-data-offset
587 (* length sb!vm:n-byte-bits))
590 ;;; the N-BIN method for FD-STREAMs
592 ;;; Note that this blocks in UNIX-READ. It is generally used where
593 ;;; there is a definite amount of reading to be done, so blocking
594 ;;; isn't too problematical.
595 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p)
596 (declare (type fd-stream stream))
597 (declare (type index start requested))
598 (do ((total-copied 0))
600 (declare (type index total-copied))
601 (let* ((remaining-request (- requested total-copied))
602 (head (fd-stream-ibuf-head stream))
603 (tail (fd-stream-ibuf-tail stream))
604 (available (- tail head))
605 (n-this-copy (min remaining-request available))
606 (this-start (+ start total-copied))
607 (this-end (+ this-start n-this-copy))
608 (sap (fd-stream-ibuf-sap stream)))
609 (declare (type index remaining-request head tail available))
610 (declare (type index n-this-copy))
611 ;; Copy data from stream buffer into user's buffer.
612 (%byte-blt sap head buffer this-start this-end)
613 (incf (fd-stream-ibuf-head stream) n-this-copy)
614 (incf total-copied n-this-copy)
615 ;; Maybe we need to refill the stream buffer.
616 (cond (;; If there were enough data in the stream buffer, we're done.
617 (= total-copied requested)
618 (return total-copied))
619 (;; If EOF, we're done in another way.
620 (zerop (refill-fd-stream-buffer stream))
622 (error 'end-of-file :stream stream)
623 (return total-copied)))
624 ;; Otherwise we refilled the stream buffer, so fall
625 ;; through into another pass of the loop.
628 ;;; Try to refill the stream buffer. Return the number of bytes read.
629 ;;; (For EOF, the return value will be zero, otherwise positive.)
630 (defun refill-fd-stream-buffer (stream)
631 ;; We don't have any logic to preserve leftover bytes in the buffer,
632 ;; so we should only be called when the buffer is empty.
633 (aver (= (fd-stream-ibuf-head stream) (fd-stream-ibuf-tail stream)))
634 (multiple-value-bind (count err)
635 (sb!unix:unix-read (fd-stream-fd stream)
636 (fd-stream-ibuf-sap stream)
637 (fd-stream-ibuf-length stream))
638 (declare (type (or index null) count))
640 (simple-stream-perror "couldn't read from ~S" stream err))
641 (setf (fd-stream-listen stream) nil
642 (fd-stream-ibuf-head stream) 0
643 (fd-stream-ibuf-tail stream) count)
646 ;;;; utility functions (misc routines, etc)
648 ;;; Fill in the various routine slots for the given type. INPUT-P and
649 ;;; OUTPUT-P indicate what slots to fill. The buffering slot must be
650 ;;; set prior to calling this routine.
651 (defun set-fd-stream-routines (fd-stream type input-p output-p buffer-p)
652 (let ((target-type (case type
653 ((:default unsigned-byte)
664 (when (fd-stream-obuf-sap fd-stream)
665 (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
666 (setf (fd-stream-obuf-sap fd-stream) nil))
667 (when (fd-stream-ibuf-sap fd-stream)
668 (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
669 (setf (fd-stream-ibuf-sap fd-stream) nil))
672 (multiple-value-bind (routine type size)
673 (pick-input-routine target-type)
675 (error "could not find any input routine for ~S" target-type))
676 (setf (fd-stream-ibuf-sap fd-stream) (next-available-buffer))
677 (setf (fd-stream-ibuf-length fd-stream) bytes-per-buffer)
678 (setf (fd-stream-ibuf-tail fd-stream) 0)
679 (if (subtypep type 'character)
680 (setf (fd-stream-in fd-stream) routine
681 (fd-stream-bin fd-stream) #'ill-bin)
682 (setf (fd-stream-in fd-stream) #'ill-in
683 (fd-stream-bin fd-stream) routine))
685 (setf (fd-stream-n-bin fd-stream) #'fd-stream-read-n-bytes)
687 (setf (ansi-stream-in-buffer fd-stream)
688 (make-array +ansi-stream-in-buffer-length+
689 :element-type '(unsigned-byte 8)))))
690 (setf input-size size)
691 (setf input-type type)))
694 (multiple-value-bind (routine type size)
695 (pick-output-routine target-type (fd-stream-buffering fd-stream))
697 (error "could not find any output routine for ~S buffered ~S"
698 (fd-stream-buffering fd-stream)
700 (setf (fd-stream-obuf-sap fd-stream) (next-available-buffer))
701 (setf (fd-stream-obuf-length fd-stream) bytes-per-buffer)
702 (setf (fd-stream-obuf-tail fd-stream) 0)
703 (if (subtypep type 'character)
704 (setf (fd-stream-out fd-stream) routine
705 (fd-stream-bout fd-stream) #'ill-bout)
706 (setf (fd-stream-out fd-stream)
708 (pick-output-routine 'base-char
709 (fd-stream-buffering fd-stream)))
711 (fd-stream-bout fd-stream) routine))
712 (setf (fd-stream-sout fd-stream)
713 (if (eql size 1) #'fd-sout #'ill-out))
714 (setf (fd-stream-char-pos fd-stream) 0)
715 (setf output-size size)
716 (setf output-type type)))
718 (when (and input-size output-size
719 (not (eq input-size output-size)))
720 (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
721 input-type input-size
722 output-type output-size))
723 (setf (fd-stream-element-size fd-stream)
724 (or input-size output-size))
726 (setf (fd-stream-element-type fd-stream)
727 (cond ((equal input-type output-type)
733 ((subtypep input-type output-type)
735 ((subtypep output-type input-type)
738 (error "Input type (~S) and output type (~S) are unrelated?"
742 ;;; Handle miscellaneous operations on FD-STREAM.
743 (defun fd-stream-misc-routine (fd-stream operation &optional arg1 arg2)
744 (declare (ignore arg2))
747 (or (not (eql (fd-stream-ibuf-head fd-stream)
748 (fd-stream-ibuf-tail fd-stream)))
749 (fd-stream-listen fd-stream)
750 (setf (fd-stream-listen fd-stream)
751 (eql (sb!alien:with-alien ((read-fds (sb!alien:struct
753 (sb!unix:fd-zero read-fds)
754 (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
755 (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
756 (sb!alien:addr read-fds)
760 (setf (fd-stream-unread fd-stream) arg1)
761 (setf (fd-stream-listen fd-stream) t))
764 ;; We got us an abort on our hands.
765 (when (fd-stream-handler fd-stream)
766 (sb!sys:remove-fd-handler (fd-stream-handler fd-stream))
767 (setf (fd-stream-handler fd-stream) nil))
768 (when (and (fd-stream-file fd-stream)
769 (fd-stream-obuf-sap fd-stream))
770 ;; We can't do anything unless we know what file were
771 ;; dealing with, and we don't want to do anything
772 ;; strange unless we were writing to the file.
773 (if (fd-stream-original fd-stream)
774 ;; We have a handle on the original, just revert.
775 (multiple-value-bind (okay err)
776 (sb!unix:unix-rename (fd-stream-original fd-stream)
777 (fd-stream-file fd-stream))
779 (simple-stream-perror
780 "couldn't restore ~S to its original contents"
783 ;; We can't restore the original, so nuke that puppy.
784 (multiple-value-bind (okay err)
785 (sb!unix:unix-unlink (fd-stream-file fd-stream))
787 (error 'simple-file-error
788 :pathname (fd-stream-file fd-stream)
790 "~@<couldn't remove ~S: ~2I~_~A~:>"
791 :format-arguments (list (fd-stream-file fd-stream)
792 (strerror err))))))))
794 (fd-stream-misc-routine fd-stream :finish-output)
795 (when (and (fd-stream-original fd-stream)
796 (fd-stream-delete-original fd-stream))
797 (multiple-value-bind (okay err)
798 (sb!unix:unix-unlink (fd-stream-original fd-stream))
800 (error 'simple-file-error
801 :pathname (fd-stream-original fd-stream)
803 "~@<couldn't delete ~S during close of ~S: ~
806 (list (fd-stream-original fd-stream)
808 (strerror err))))))))
809 (when (fboundp 'cancel-finalization)
810 (cancel-finalization fd-stream))
811 (sb!unix:unix-close (fd-stream-fd fd-stream))
812 (when (fd-stream-obuf-sap fd-stream)
813 (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
814 (setf (fd-stream-obuf-sap fd-stream) nil))
815 (when (fd-stream-ibuf-sap fd-stream)
816 (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
817 (setf (fd-stream-ibuf-sap fd-stream) nil))
818 (sb!impl::set-closed-flame fd-stream))
820 (setf (fd-stream-unread fd-stream) nil)
821 (setf (fd-stream-ibuf-head fd-stream) 0)
822 (setf (fd-stream-ibuf-tail fd-stream) 0)
823 (catch 'eof-input-catcher
825 (let ((count (sb!alien:with-alien ((read-fds (sb!alien:struct
827 (sb!unix:fd-zero read-fds)
828 (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
829 (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
830 (sb!alien:addr read-fds)
836 (frob-input fd-stream)
837 (setf (fd-stream-ibuf-head fd-stream) 0)
838 (setf (fd-stream-ibuf-tail fd-stream) 0))
842 (flush-output-buffer fd-stream))
844 (flush-output-buffer fd-stream)
846 ((null (fd-stream-output-later fd-stream)))
847 (sb!sys:serve-all-events)))
849 (fd-stream-element-type fd-stream))
851 ;; FIXME: sb!unix:unix-isatty is undefined.
852 (sb!unix:unix-isatty (fd-stream-fd fd-stream)))
856 (fd-stream-char-pos fd-stream))
858 (unless (fd-stream-file fd-stream)
859 ;; This is a TYPE-ERROR because ANSI's species FILE-LENGTH
860 ;; "should signal an error of type TYPE-ERROR if stream is not
861 ;; a stream associated with a file". Too bad there's no very
862 ;; appropriate value for the EXPECTED-TYPE slot..
863 (error 'simple-type-error
865 :expected-type 'file-stream
866 :format-control "~S is not a stream associated with a file."
867 :format-arguments (list fd-stream)))
868 (multiple-value-bind (okay dev ino mode nlink uid gid rdev size
869 atime mtime ctime blksize blocks)
870 (sb!unix:unix-fstat (fd-stream-fd fd-stream))
871 (declare (ignore ino nlink uid gid rdev
872 atime mtime ctime blksize blocks))
874 (simple-stream-perror "failed Unix fstat(2) on ~S" fd-stream dev))
877 (truncate size (fd-stream-element-size fd-stream)))))
879 (fd-stream-file-position fd-stream arg1))))
881 (defun fd-stream-file-position (stream &optional newpos)
882 (declare (type fd-stream stream)
883 (type (or index (member nil :start :end)) newpos))
885 (sb!sys:without-interrupts
886 ;; First, find the position of the UNIX file descriptor in the file.
887 (multiple-value-bind (posn errno)
888 (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr)
889 (declare (type (or index null) posn))
890 (cond ((fixnump posn)
891 ;; Adjust for buffered output: If there is any output
892 ;; buffered, the *real* file position will be larger
893 ;; than reported by lseek() because lseek() obviously
894 ;; cannot take into account output we have not sent
896 (dolist (later (fd-stream-output-later stream))
897 (incf posn (- (the index (caddr later))
898 (the index (cadr later)))))
899 (incf posn (fd-stream-obuf-tail stream))
900 ;; Adjust for unread input: If there is any input
901 ;; read from UNIX but not supplied to the user of the
902 ;; stream, the *real* file position will smaller than
903 ;; reported, because we want to look like the unread
904 ;; stuff is still available.
905 (decf posn (- (fd-stream-ibuf-tail stream)
906 (fd-stream-ibuf-head stream)))
907 (when (fd-stream-unread stream)
909 ;; Divide bytes by element size.
910 (truncate posn (fd-stream-element-size stream)))
911 ((eq errno sb!unix:espipe)
914 (sb!sys:with-interrupts
915 (simple-stream-perror "failure in Unix lseek() on ~S"
918 (let ((offset 0) origin)
919 (declare (type index offset))
920 ;; Make sure we don't have any output pending, because if we
921 ;; move the file pointer before writing this stuff, it will be
922 ;; written in the wrong location.
923 (flush-output-buffer stream)
925 ((null (fd-stream-output-later stream)))
926 (sb!sys:serve-all-events))
927 ;; Clear out any pending input to force the next read to go to
929 (setf (fd-stream-unread stream) nil)
930 (setf (fd-stream-ibuf-head stream) 0)
931 (setf (fd-stream-ibuf-tail stream) 0)
932 ;; Trash cached value for listen, so that we check next time.
933 (setf (fd-stream-listen stream) nil)
935 (cond ((eq newpos :start)
936 (setf offset 0 origin sb!unix:l_set))
938 (setf offset 0 origin sb!unix:l_xtnd))
939 ((typep newpos 'index)
940 (setf offset (* newpos (fd-stream-element-size stream))
941 origin sb!unix:l_set))
943 (error "invalid position given to FILE-POSITION: ~S" newpos)))
944 (multiple-value-bind (posn errno)
945 (sb!unix:unix-lseek (fd-stream-fd stream) offset origin)
946 (cond ((typep posn 'fixnum)
948 ((eq errno sb!unix:espipe)
951 (simple-stream-perror "error in Unix lseek() on ~S"
955 ;;;; creation routines (MAKE-FD-STREAM and OPEN)
957 ;;; Create a stream for the given Unix file descriptor.
959 ;;; If INPUT is non-NIL, allow input operations. If OUTPUT is non-nil,
960 ;;; allow output operations. If neither INPUT nor OUTPUT is specified,
961 ;;; default to allowing input.
963 ;;; ELEMENT-TYPE indicates the element type to use (as for OPEN).
965 ;;; BUFFERING indicates the kind of buffering to use.
967 ;;; TIMEOUT (if true) is the number of seconds to wait for input. If
968 ;;; NIL (the default), then wait forever. When we time out, we signal
971 ;;; FILE is the name of the file (will be returned by PATHNAME).
973 ;;; NAME is used to identify the stream when printed.
974 (defun make-fd-stream (fd
977 (output nil output-p)
978 (element-type 'base-char)
987 (format nil "file ~S" file)
988 (format nil "descriptor ~W" fd)))
990 (declare (type index fd) (type (or index null) timeout)
991 (type (member :none :line :full) buffering))
992 (cond ((not (or input-p output-p))
994 ((not (or input output))
995 (error "File descriptor must be opened either for input or output.")))
996 (let ((stream (%make-fd-stream :fd fd
1000 :delete-original delete-original
1002 :buffering buffering
1004 (set-fd-stream-routines stream element-type input output input-buffer-p)
1005 (when (and auto-close (fboundp 'finalize))
1008 (sb!unix:unix-close fd)
1010 (format *terminal-io* "** closed file descriptor ~W **~%"
1014 ;;; Pick a name to use for the backup file for the :IF-EXISTS
1015 ;;; :RENAME-AND-DELETE and :RENAME options.
1016 (defun pick-backup-name (name)
1017 (declare (type simple-string name))
1018 (concatenate 'simple-string name ".bak"))
1020 ;;; Ensure that the given arg is one of the given list of valid
1021 ;;; things. Allow the user to fix any problems.
1022 (defun ensure-one-of (item list what)
1023 (unless (member item list)
1024 (error 'simple-type-error
1026 :expected-type `(member ,@list)
1027 :format-control "~@<~S is ~_invalid for ~S; ~_need one of~{ ~S~}~:>"
1028 :format-arguments (list item what list))))
1030 ;;; Rename NAMESTRING to ORIGINAL. First, check whether we have write
1031 ;;; access, since we don't want to trash unwritable files even if we
1032 ;;; technically can. We return true if we succeed in renaming.
1033 (defun rename-the-old-one (namestring original)
1034 (unless (sb!unix:unix-access namestring sb!unix:w_ok)
1035 (error "~@<The file ~2I~_~S ~I~_is not writable.~:>" namestring))
1036 (multiple-value-bind (okay err) (sb!unix:unix-rename namestring original)
1039 (error 'simple-file-error
1040 :pathname namestring
1042 "~@<couldn't rename ~2I~_~S ~I~_to ~2I~_~S: ~4I~_~A~:>"
1043 :format-arguments (list namestring original (strerror err))))))
1045 (defun open (filename
1048 (element-type 'base-char)
1049 (if-exists nil if-exists-given)
1050 (if-does-not-exist nil if-does-not-exist-given)
1051 (external-format :default)
1052 &aux ; Squelch assignment warning.
1053 (direction direction)
1054 (if-does-not-exist if-does-not-exist)
1055 (if-exists if-exists))
1057 "Return a stream which reads from or writes to FILENAME.
1059 :DIRECTION - one of :INPUT, :OUTPUT, :IO, or :PROBE
1060 :ELEMENT-TYPE - the type of object to read or write, default BASE-CHAR
1061 :IF-EXISTS - one of :ERROR, :NEW-VERSION, :RENAME, :RENAME-AND-DELETE,
1062 :OVERWRITE, :APPEND, :SUPERSEDE or NIL
1063 :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or nil
1064 See the manual for details."
1066 (unless (eq external-format :default)
1067 (error "Any external format other than :DEFAULT isn't recognized."))
1069 ;; First, make sure that DIRECTION is valid.
1070 (ensure-one-of direction
1071 '(:input :output :io :probe)
1074 ;; Calculate useful stuff.
1075 (multiple-value-bind (input output mask)
1077 (:input (values t nil sb!unix:o_rdonly))
1078 (:output (values nil t sb!unix:o_wronly))
1079 (:io (values t t sb!unix:o_rdwr))
1080 (:probe (values t nil sb!unix:o_rdonly)))
1081 (declare (type index mask))
1082 (let* ((pathname (merge-pathnames filename))
1084 (cond ((unix-namestring pathname input))
1085 ((and input (eq if-does-not-exist :create))
1086 (unix-namestring pathname nil)))))
1087 ;; Process if-exists argument if we are doing any output.
1089 (unless if-exists-given
1091 (if (eq (pathname-version pathname) :newest)
1094 (ensure-one-of if-exists
1095 '(:error :new-version :rename
1096 :rename-and-delete :overwrite
1097 :append :supersede nil)
1101 (setf mask (logior mask sb!unix:o_excl)))
1102 ((:rename :rename-and-delete)
1103 (setf mask (logior mask sb!unix:o_creat)))
1104 ((:new-version :supersede)
1105 (setf mask (logior mask sb!unix:o_trunc)))
1107 (setf mask (logior mask sb!unix:o_append)))))
1109 (setf if-exists :ignore-this-arg)))
1111 (unless if-does-not-exist-given
1112 (setf if-does-not-exist
1113 (cond ((eq direction :input) :error)
1115 (member if-exists '(:overwrite :append)))
1117 ((eq direction :probe)
1121 (ensure-one-of if-does-not-exist
1122 '(:error :create nil)
1124 (if (eq if-does-not-exist :create)
1125 (setf mask (logior mask sb!unix:o_creat)))
1127 (let ((original (if (member if-exists
1128 '(:rename :rename-and-delete))
1129 (pick-backup-name namestring)))
1130 (delete-original (eq if-exists :rename-and-delete))
1133 ;; We are doing a :RENAME or :RENAME-AND-DELETE. Determine
1134 ;; whether the file already exists, make sure the original
1135 ;; file is not a directory, and keep the mode.
1138 (multiple-value-bind (okay err/dev inode orig-mode)
1139 (sb!unix:unix-stat namestring)
1140 (declare (ignore inode)
1141 (type (or index null) orig-mode))
1144 (when (and output (= (logand orig-mode #o170000)
1146 (error 'simple-file-error
1147 :pathname namestring
1149 "can't open ~S for output: is a directory"
1150 :format-arguments (list namestring)))
1151 (setf mode (logand orig-mode #o777))
1153 ((eql err/dev sb!unix:enoent)
1156 (simple-file-perror "can't find ~S"
1160 (rename-the-old-one namestring original))
1162 (setf delete-original nil)
1163 ;; In order to use :SUPERSEDE instead, we have to make
1164 ;; sure SB!UNIX:O_CREAT corresponds to
1165 ;; IF-DOES-NOT-EXIST. SB!UNIX:O_CREAT was set before
1166 ;; because of IF-EXISTS being :RENAME.
1167 (unless (eq if-does-not-exist :create)
1169 (logior (logandc2 mask sb!unix:o_creat)
1171 (setf if-exists :supersede))))
1173 ;; Now we can try the actual Unix open(2).
1174 (multiple-value-bind (fd errno)
1176 (sb!unix:unix-open namestring mask mode)
1177 (values nil sb!unix:enoent))
1178 (labels ((open-error (format-control &rest format-arguments)
1179 (error 'simple-file-error
1181 :format-control format-control
1182 :format-arguments format-arguments))
1183 (vanilla-open-error ()
1184 (simple-file-perror "error opening ~S" pathname errno)))
1187 ((:input :output :io)
1191 :element-type element-type
1194 :delete-original delete-original
1200 (%make-fd-stream :name namestring
1203 :element-type element-type)))
1206 ((eql errno sb!unix:enoent)
1207 (case if-does-not-exist
1208 (:error (vanilla-open-error))
1210 (open-error "~@<The path ~2I~_~S ~I~_does not exist.~:>"
1213 ((and (eql errno sb!unix:eexist) if-exists)
1216 (vanilla-open-error)))))))))
1220 ;;; the stream connected to the controlling terminal, or NIL if there is none
1223 ;;; the stream connected to the standard input (file descriptor 0)
1226 ;;; the stream connected to the standard output (file descriptor 1)
1229 ;;; the stream connected to the standard error output (file descriptor 2)
1232 ;;; This is called when the cold load is first started up, and may also
1233 ;;; be called in an attempt to recover from nested errors.
1234 (defun stream-cold-init-or-reset ()
1236 (setf *terminal-io* (make-synonym-stream '*tty*))
1237 (setf *standard-output* (make-synonym-stream '*stdout*))
1238 (setf *standard-input*
1240 ;; FIXME: Why is *STANDARD-INPUT* a TWO-WAY-STREAM? ANSI says
1241 ;; it's an input stream.
1244 %make-two-way-stream (make-synonym-stream '*stdin*)
1246 (setf *error-output* (make-synonym-stream '*stderr*))
1247 (setf *query-io* (make-synonym-stream '*terminal-io*))
1248 (setf *debug-io* *query-io*)
1249 (setf *trace-output* *standard-output*)
1252 ;;; This is called whenever a saved core is restarted.
1253 (defun stream-reinit ()
1254 (setf *available-buffers* nil)
1256 (make-fd-stream 0 :name "standard input" :input t :buffering :line))
1258 (make-fd-stream 1 :name "standard output" :output t :buffering :line))
1260 (make-fd-stream 2 :name "standard error" :output t :buffering :line))
1261 (let ((tty (sb!unix:unix-open "/dev/tty" sb!unix:o_rdwr #o666)))
1265 :name "the terminal"
1270 (setf *tty* (make-two-way-stream *stdin* *stdout*))))
1275 ;;; the Unix way to beep
1276 (defun beep (stream)
1277 (write-char (code-char bell-char-code) stream)
1278 (finish-output stream))
1280 ;;; This is kind of like FILE-POSITION, but is an internal hack used
1281 ;;; by the filesys stuff to get and set the file name.
1283 ;;; FIXME: misleading name, screwy interface
1284 (defun file-name (stream &optional new-name)
1285 (when (typep stream 'fd-stream)
1287 (setf (fd-stream-pathname stream) new-name)
1288 (setf (fd-stream-file stream)
1289 (unix-namestring new-name nil))
1292 (fd-stream-pathname stream)))))
1294 ;;;; international character support (which is trivial for our simple
1295 ;;;; character sets)
1297 ;;;; (Those who do Lisp only in English might not remember that ANSI
1298 ;;;; requires these functions to be exported from package
1301 (defun file-string-length (stream object)
1302 (declare (type (or string character) object) (type file-stream stream))
1304 "Return the delta in STREAM's FILE-POSITION that would be caused by writing
1305 OBJECT to STREAM. Non-trivial only in implementations that support
1306 international character sets."
1307 (declare (ignore stream))
1310 (string (length object))))
1312 (defun stream-external-format (stream)
1313 (declare (type file-stream stream) (ignore stream))