0.8.7.38:
[sbcl/lichteblau.git] / src / code / fd-stream.lisp
blob3c2f2867fa0a848cf0b0c327dd50a9b3522952c5
1 ;;;; streams for UNIX file descriptors
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.
12 (in-package "SB!IMPL")
14 ;;;; buffer manipulation routines
16 ;;; FIXME: Is it really good to maintain this pool separate from the
17 ;;; GC and the C malloc logic?
18 (defvar *available-buffers* ()
19 #!+sb-doc
20 "List of available buffers. Each buffer is an sap pointing to
21 bytes-per-buffer of memory.")
23 (defconstant bytes-per-buffer (* 4 1024)
24 #!+sb-doc
25 "Number of bytes per buffer.")
27 ;;; Return the next available buffer, creating one if necessary.
28 #!-sb-fluid (declaim (inline next-available-buffer))
29 (defun next-available-buffer ()
30 (if *available-buffers*
31 (pop *available-buffers*)
32 (allocate-system-memory bytes-per-buffer)))
34 ;;;; the FILE-STREAM structure
36 (defstruct (file-stream
37 (:constructor %make-fd-stream)
38 ;; KLUDGE: in an ideal world, maybe we'd rewrite
39 ;; everything to use FILE-STREAM rather than simply
40 ;; providing this hack for compatibility with the old
41 ;; code. However, CVS doesn't deal terribly well with
42 ;; file renaming, so for now we use this
43 ;; backward-compatibility feature.
44 (:conc-name fd-stream-)
45 (:predicate fd-stream-p)
46 (:include ansi-stream
47 (misc #'fd-stream-misc-routine))
48 (:copier nil))
50 ;; the name of this stream
51 (name nil)
52 ;; the file this stream is for
53 (file nil)
54 ;; the backup file namestring for the old file, for :IF-EXISTS
55 ;; :RENAME or :RENAME-AND-DELETE.
56 (original nil :type (or simple-string null))
57 (delete-original nil) ; for :if-exists :rename-and-delete
58 ;;; the number of bytes per element
59 (element-size 1 :type index)
60 ;; the type of element being transfered
61 (element-type 'base-char)
62 ;; the Unix file descriptor
63 (fd -1 :type fixnum)
64 ;; controls when the output buffer is flushed
65 (buffering :full :type (member :full :line :none))
66 ;; character position (if known)
67 (char-pos nil :type (or index null))
68 ;; T if input is waiting on FD. :EOF if we hit EOF.
69 (listen nil :type (member nil t :eof))
71 ;; the input buffer
72 (unread nil)
73 (ibuf-sap nil :type (or system-area-pointer null))
74 (ibuf-length nil :type (or index null))
75 (ibuf-head 0 :type index)
76 (ibuf-tail 0 :type index)
78 ;; the output buffer
79 (obuf-sap nil :type (or system-area-pointer null))
80 (obuf-length nil :type (or index null))
81 (obuf-tail 0 :type index)
83 ;; output flushed, but not written due to non-blocking io?
84 (output-later nil)
85 (handler nil)
86 ;; timeout specified for this stream, or NIL if none
87 (timeout nil :type (or index null))
88 ;; pathname of the file this stream is opened to (returned by PATHNAME)
89 (pathname nil :type (or pathname null)))
90 (def!method print-object ((fd-stream file-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* ()
98 #!+sb-doc
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
106 :stream stream
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
111 :pathname pathname
112 :format-control "~@<~?: ~2I~_~A~:>"
113 :format-arguments
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
119 ;;; is wrong.
120 (defun frob-output-later (stream)
121 (let* ((stuff (pop (fd-stream-output-later stream)))
122 (base (car stuff))
123 (start (cadr stuff))
124 (end (caddr stuff))
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)
130 base
131 start
132 length)
133 (cond ((not count)
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.
138 (when reuse-sap
139 (push base *available-buffers*)))
140 ((not (null count)) ; sorta worked..
141 (push (list base
142 (the index (+ start count))
143 end)
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)
156 :output
157 (lambda (fd)
158 (declare (ignore fd))
159 (frob-output-later stream)))))
161 (nconc (fd-stream-output-later stream)
162 (list (list base start end reuse-sap)))))
163 (when 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 file-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.
176 (progn
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)
183 (cond ((not count)
184 (if (= errno sb!unix:ewouldblock)
185 (output-later stream base start end reuse-sap)
186 (simple-stream-perror "couldn't write to ~S"
187 stream
188 errno)))
189 ((not (eql count length))
190 (output-later stream base (the index (+ start count))
191 end reuse-sap)))))))
193 ;;; Flush any data in the output buffer.
194 (defun flush-output-buffer (stream)
195 (let ((length (fd-stream-obuf-tail stream)))
196 (unless (= length 0)
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)))
204 (cons 'progn
205 (mapcar
206 (lambda (buffering)
207 (let ((function
208 (intern (let ((*print-case* :upcase))
209 (format nil name-fmt (car buffering))))))
210 `(progn
211 (defun ,function (stream byte)
212 ,(unless (eq (car buffering) :none)
213 `(when (< (fd-stream-obuf-length stream)
214 (+ (fd-stream-obuf-tail stream)
215 ,size))
216 (flush-output-buffer stream)))
217 ,(unless (eq (car buffering) :none)
218 `(when (> (fd-stream-ibuf-tail stream)
219 (fd-stream-ibuf-head stream))
220 (file-position stream (file-position stream))))
222 ,@body
223 (incf (fd-stream-obuf-tail stream) ,size)
224 ,(ecase (car buffering)
225 (:none
226 `(flush-output-buffer stream))
227 (:line
228 `(when (eq (char-code byte) (char-code #\Newline))
229 (flush-output-buffer stream)))
230 (:full
232 (values))
233 (setf *output-routines*
234 (nconc *output-routines*
235 ',(mapcar
236 (lambda (type)
237 (list type
238 (car buffering)
239 function
240 size))
241 (cdr buffering)))))))
242 bufferings)))
244 (def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
246 (:none character)
247 (:line character)
248 (:full character))
249 (if (and (base-char-p byte) (char= byte #\Newline))
250 (setf (fd-stream-char-pos stream) 0)
251 (incf (fd-stream-char-pos stream)))
252 (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
253 (char-code byte)))
255 (def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
257 (:none (unsigned-byte 8))
258 (:full (unsigned-byte 8)))
259 (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
260 byte))
262 (def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
264 (:none (signed-byte 8))
265 (:full (signed-byte 8)))
266 (setf (signed-sap-ref-8 (fd-stream-obuf-sap stream)
267 (fd-stream-obuf-tail stream))
268 byte))
270 (def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
272 (:none (unsigned-byte 16))
273 (:full (unsigned-byte 16)))
274 (setf (sap-ref-16 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
275 byte))
277 (def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
279 (:none (signed-byte 16))
280 (:full (signed-byte 16)))
281 (setf (signed-sap-ref-16 (fd-stream-obuf-sap stream)
282 (fd-stream-obuf-tail stream))
283 byte))
285 (def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
287 (:none (unsigned-byte 32))
288 (:full (unsigned-byte 32)))
289 (setf (sap-ref-32 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
290 byte))
292 (def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
294 (:none (signed-byte 32))
295 (:full (signed-byte 32)))
296 (setf (signed-sap-ref-32 (fd-stream-obuf-sap stream)
297 (fd-stream-obuf-tail stream))
298 byte))
300 ;;; Do the actual output. If there is space to buffer the string,
301 ;;; buffer it. If the string would normally fit in the buffer, but
302 ;;; doesn't because of other stuff in the buffer, flush the old noise
303 ;;; out of the buffer and put the string in it. Otherwise we have a
304 ;;; very long string, so just send it directly (after flushing the
305 ;;; buffer, of course).
306 (defun output-raw-bytes (fd-stream thing &optional start end)
307 #!+sb-doc
308 "Output THING to FD-STREAM. THING can be any kind of vector or a SAP. If
309 THING is a SAP, END must be supplied (as length won't work)."
310 (let ((start (or start 0))
311 (end (or end (length (the (simple-array * (*)) thing)))))
312 (declare (type index start end))
313 (when (> (fd-stream-ibuf-tail fd-stream)
314 (fd-stream-ibuf-head fd-stream))
315 (file-position fd-stream (file-position fd-stream)))
316 (let* ((len (fd-stream-obuf-length fd-stream))
317 (tail (fd-stream-obuf-tail fd-stream))
318 (space (- len tail))
319 (bytes (- end start))
320 (newtail (+ tail bytes)))
321 (cond ((minusp bytes) ; error case
322 (error ":END before :START!"))
323 ((zerop bytes)) ; easy case
324 ((<= bytes space)
325 (if (system-area-pointer-p thing)
326 (system-area-copy thing
327 (* start sb!vm:n-byte-bits)
328 (fd-stream-obuf-sap fd-stream)
329 (* tail sb!vm:n-byte-bits)
330 (* bytes sb!vm:n-byte-bits))
331 ;; FIXME: There should be some type checking somewhere to
332 ;; verify that THING here is a vector, not just <not a SAP>.
333 (copy-to-system-area thing
334 (+ (* start sb!vm:n-byte-bits)
335 (* sb!vm:vector-data-offset
336 sb!vm:n-word-bits))
337 (fd-stream-obuf-sap fd-stream)
338 (* tail sb!vm:n-byte-bits)
339 (* bytes sb!vm:n-byte-bits)))
340 (setf (fd-stream-obuf-tail fd-stream) newtail))
341 ((<= bytes len)
342 (flush-output-buffer fd-stream)
343 (if (system-area-pointer-p thing)
344 (system-area-copy thing
345 (* start sb!vm:n-byte-bits)
346 (fd-stream-obuf-sap fd-stream)
348 (* bytes sb!vm:n-byte-bits))
349 ;; FIXME: There should be some type checking somewhere to
350 ;; verify that THING here is a vector, not just <not a SAP>.
351 (copy-to-system-area thing
352 (+ (* start sb!vm:n-byte-bits)
353 (* sb!vm:vector-data-offset
354 sb!vm:n-word-bits))
355 (fd-stream-obuf-sap fd-stream)
357 (* bytes sb!vm:n-byte-bits)))
358 (setf (fd-stream-obuf-tail fd-stream) bytes))
360 (flush-output-buffer fd-stream)
361 (frob-output fd-stream thing start end nil))))))
363 ;;; the routine to use to output a string. If the stream is
364 ;;; unbuffered, slam the string down the file descriptor, otherwise
365 ;;; use OUTPUT-RAW-BYTES to buffer the string. Update charpos by
366 ;;; checking to see where the last newline was.
368 ;;; Note: some bozos (the FASL dumper) call write-string with things
369 ;;; other than strings. Therefore, we must make sure we have a string
370 ;;; before calling POSITION on it.
371 ;;; KLUDGE: It would be better to fix the bozos instead of trying to
372 ;;; cover for them here. -- WHN 20000203
373 (defun fd-sout (stream thing start end)
374 (let ((start (or start 0))
375 (end (or end (length (the vector thing)))))
376 (declare (fixnum start end))
377 (if (stringp thing)
378 (let ((last-newline (and (find #\newline (the simple-string thing)
379 :start start :end end)
380 ;; FIXME why do we need both calls?
381 ;; Is find faster forwards than
382 ;; position is backwards?
383 (position #\newline (the simple-string thing)
384 :from-end t
385 :start start
386 :end end))))
387 (ecase (fd-stream-buffering stream)
388 (:full
389 (output-raw-bytes stream thing start end))
390 (:line
391 (output-raw-bytes stream thing start end)
392 (when last-newline
393 (flush-output-buffer stream)))
394 (:none
395 (frob-output stream thing start end nil)))
396 (if last-newline
397 (setf (fd-stream-char-pos stream)
398 (- end last-newline 1))
399 (incf (fd-stream-char-pos stream)
400 (- end start))))
401 (ecase (fd-stream-buffering stream)
402 ((:line :full)
403 (output-raw-bytes stream thing start end))
404 (:none
405 (frob-output stream thing start end nil))))))
407 ;;; Find an output routine to use given the type and buffering. Return
408 ;;; as multiple values the routine, the real type transfered, and the
409 ;;; number of bytes per element.
410 (defun pick-output-routine (type buffering)
411 (dolist (entry *output-routines*)
412 (when (and (subtypep type (car entry))
413 (eq buffering (cadr entry)))
414 (return (values (symbol-function (caddr entry))
415 (car entry)
416 (cadddr entry))))))
418 ;;;; input routines and related noise
420 ;;; a list of all available input routines. Each element is a list of
421 ;;; the element-type input, the function name, and the number of bytes
422 ;;; per element.
423 (defvar *input-routines* ())
425 ;;; Fill the input buffer, and return the first character. Throw to
426 ;;; EOF-INPUT-CATCHER if the eof was reached. Drop into SYSTEM:SERVER
427 ;;; if necessary.
428 (defun frob-input (stream)
429 (let ((fd (fd-stream-fd stream))
430 (ibuf-sap (fd-stream-ibuf-sap stream))
431 (buflen (fd-stream-ibuf-length stream))
432 (head (fd-stream-ibuf-head stream))
433 (tail (fd-stream-ibuf-tail stream)))
434 (declare (type index head tail))
435 (unless (zerop head)
436 (cond ((eql head tail)
437 (setf head 0)
438 (setf tail 0)
439 (setf (fd-stream-ibuf-head stream) 0)
440 (setf (fd-stream-ibuf-tail stream) 0))
442 (decf tail head)
443 (system-area-copy ibuf-sap (* head sb!vm:n-byte-bits)
444 ibuf-sap 0 (* tail sb!vm:n-byte-bits))
445 (setf head 0)
446 (setf (fd-stream-ibuf-head stream) 0)
447 (setf (fd-stream-ibuf-tail stream) tail))))
448 (setf (fd-stream-listen stream) nil)
449 (multiple-value-bind (count errno)
450 ;; FIXME: Judging from compiler warnings, this WITH-ALIEN form expands
451 ;; into something which uses the not-yet-defined type
452 ;; (SB!ALIEN-INTERNALS:ALIEN (* (SB!ALIEN:STRUCT SB!UNIX:FD-SET))).
453 ;; This is probably inefficient and unsafe and generally bad, so
454 ;; try to find some way to make that type known before
455 ;; this is compiled.
456 (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set)))
457 (sb!unix:fd-zero read-fds)
458 (sb!unix:fd-set fd read-fds)
459 (sb!unix:unix-fast-select (1+ fd)
460 (sb!alien:addr read-fds)
465 (case count
468 (unless (sb!sys:wait-until-fd-usable
469 fd :input (fd-stream-timeout stream))
470 (error 'io-timeout :stream stream :direction :read)))
472 (simple-stream-perror "couldn't check whether ~S is readable"
473 stream
474 errno))))
475 (multiple-value-bind (count errno)
476 (sb!unix:unix-read fd
477 (sb!sys:int-sap (+ (sb!sys:sap-int ibuf-sap) tail))
478 (- buflen tail))
479 (cond ((null count)
480 (if (eql errno sb!unix:ewouldblock)
481 (progn
482 (unless (sb!sys:wait-until-fd-usable
483 fd :input (fd-stream-timeout stream))
484 (error 'io-timeout :stream stream :direction :read))
485 (frob-input stream))
486 (simple-stream-perror "couldn't read from ~S" stream errno)))
487 ((zerop count)
488 (setf (fd-stream-listen stream) :eof)
489 (/show0 "THROWing EOF-INPUT-CATCHER")
490 (throw 'eof-input-catcher nil))
492 (incf (fd-stream-ibuf-tail stream) count))))))
494 ;;; Make sure there are at least BYTES number of bytes in the input
495 ;;; buffer. Keep calling FROB-INPUT until that condition is met.
496 (defmacro input-at-least (stream bytes)
497 (let ((stream-var (gensym))
498 (bytes-var (gensym)))
499 `(let ((,stream-var ,stream)
500 (,bytes-var ,bytes))
501 (loop
502 (when (>= (- (fd-stream-ibuf-tail ,stream-var)
503 (fd-stream-ibuf-head ,stream-var))
504 ,bytes-var)
505 (return))
506 (frob-input ,stream-var)))))
508 ;;; a macro to wrap around all input routines to handle EOF-ERROR noise
509 (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms)
510 (let ((stream-var (gensym))
511 (element-var (gensym)))
512 `(let ((,stream-var ,stream))
513 (if (fd-stream-unread ,stream-var)
514 (prog1
515 (fd-stream-unread ,stream-var)
516 (setf (fd-stream-unread ,stream-var) nil)
517 (setf (fd-stream-listen ,stream-var) nil))
518 (let ((,element-var
519 (catch 'eof-input-catcher
520 (input-at-least ,stream-var ,bytes)
521 ,@read-forms)))
522 (cond (,element-var
523 (incf (fd-stream-ibuf-head ,stream-var) ,bytes)
524 ,element-var)
526 (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
528 (defmacro def-input-routine (name
529 (type size sap head)
530 &rest body)
531 `(progn
532 (defun ,name (stream eof-error eof-value)
533 (input-wrapper (stream ,size eof-error eof-value)
534 (let ((,sap (fd-stream-ibuf-sap stream))
535 (,head (fd-stream-ibuf-head stream)))
536 ,@body)))
537 (setf *input-routines*
538 (nconc *input-routines*
539 (list (list ',type ',name ',size))))))
541 ;;; STREAM-IN routine for reading a string char
542 (def-input-routine input-character
543 (character 1 sap head)
544 (code-char (sap-ref-8 sap head)))
546 ;;; STREAM-IN routine for reading an unsigned 8 bit number
547 (def-input-routine input-unsigned-8bit-byte
548 ((unsigned-byte 8) 1 sap head)
549 (sap-ref-8 sap head))
551 ;;; STREAM-IN routine for reading a signed 8 bit number
552 (def-input-routine input-signed-8bit-number
553 ((signed-byte 8) 1 sap head)
554 (signed-sap-ref-8 sap head))
556 ;;; STREAM-IN routine for reading an unsigned 16 bit number
557 (def-input-routine input-unsigned-16bit-byte
558 ((unsigned-byte 16) 2 sap head)
559 (sap-ref-16 sap head))
561 ;;; STREAM-IN routine for reading a signed 16 bit number
562 (def-input-routine input-signed-16bit-byte
563 ((signed-byte 16) 2 sap head)
564 (signed-sap-ref-16 sap head))
566 ;;; STREAM-IN routine for reading a unsigned 32 bit number
567 (def-input-routine input-unsigned-32bit-byte
568 ((unsigned-byte 32) 4 sap head)
569 (sap-ref-32 sap head))
571 ;;; STREAM-IN routine for reading a signed 32 bit number
572 (def-input-routine input-signed-32bit-byte
573 ((signed-byte 32) 4 sap head)
574 (signed-sap-ref-32 sap head))
576 ;;; Find an input routine to use given the type. Return as multiple
577 ;;; values the routine, the real type transfered, and the number of
578 ;;; bytes per element.
579 (defun pick-input-routine (type)
580 (dolist (entry *input-routines*)
581 (when (subtypep type (car entry))
582 (return (values (symbol-function (cadr entry))
583 (car entry)
584 (caddr entry))))))
586 ;;; Return a string constructed from SAP, START, and END.
587 (defun string-from-sap (sap start end)
588 (declare (type index start end))
589 (let* ((length (- end start))
590 (string (make-string length)))
591 (copy-from-system-area sap (* start sb!vm:n-byte-bits)
592 string (* sb!vm:vector-data-offset
593 sb!vm:n-word-bits)
594 (* length sb!vm:n-byte-bits))
595 string))
597 ;;; the N-BIN method for FD-STREAMs
599 ;;; Note that this blocks in UNIX-READ. It is generally used where
600 ;;; there is a definite amount of reading to be done, so blocking
601 ;;; isn't too problematical.
602 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p
603 &aux (total-copied 0))
604 (declare (type file-stream stream))
605 (declare (type index start requested total-copied))
606 (let ((unread (fd-stream-unread stream)))
607 (when unread
608 ;; AVERs designed to fail when we have more complicated
609 ;; character representations.
610 (aver (typep unread 'base-char))
611 (aver (= (fd-stream-element-size stream) 1))
612 ;; KLUDGE: this is a slightly-unrolled-and-inlined version of
613 ;; %BYTE-BLT
614 (etypecase buffer
615 (system-area-pointer
616 (setf (sap-ref-8 buffer start) (char-code unread)))
617 ((simple-unboxed-array (*))
618 (setf (aref buffer start) unread)))
619 (setf (fd-stream-unread stream) nil)
620 (setf (fd-stream-listen stream) nil)
621 (incf total-copied)))
622 (do ()
623 (nil)
624 (let* ((remaining-request (- requested total-copied))
625 (head (fd-stream-ibuf-head stream))
626 (tail (fd-stream-ibuf-tail stream))
627 (available (- tail head))
628 (n-this-copy (min remaining-request available))
629 (this-start (+ start total-copied))
630 (this-end (+ this-start n-this-copy))
631 (sap (fd-stream-ibuf-sap stream)))
632 (declare (type index remaining-request head tail available))
633 (declare (type index n-this-copy))
634 ;; Copy data from stream buffer into user's buffer.
635 (%byte-blt sap head buffer this-start this-end)
636 (incf (fd-stream-ibuf-head stream) n-this-copy)
637 (incf total-copied n-this-copy)
638 ;; Maybe we need to refill the stream buffer.
639 (cond (;; If there were enough data in the stream buffer, we're done.
640 (= total-copied requested)
641 (return total-copied))
642 (;; If EOF, we're done in another way.
643 (zerop (refill-fd-stream-buffer stream))
644 (if eof-error-p
645 (error 'end-of-file :stream stream)
646 (return total-copied)))
647 ;; Otherwise we refilled the stream buffer, so fall
648 ;; through into another pass of the loop.
649 ))))
651 ;;; Try to refill the stream buffer. Return the number of bytes read.
652 ;;; (For EOF, the return value will be zero, otherwise positive.)
653 (defun refill-fd-stream-buffer (stream)
654 ;; We don't have any logic to preserve leftover bytes in the buffer,
655 ;; so we should only be called when the buffer is empty.
656 (aver (= (fd-stream-ibuf-head stream) (fd-stream-ibuf-tail stream)))
657 (multiple-value-bind (count err)
658 (sb!unix:unix-read (fd-stream-fd stream)
659 (fd-stream-ibuf-sap stream)
660 (fd-stream-ibuf-length stream))
661 (declare (type (or index null) count))
662 (when (null count)
663 (simple-stream-perror "couldn't read from ~S" stream err))
664 (setf (fd-stream-listen stream) nil
665 (fd-stream-ibuf-head stream) 0
666 (fd-stream-ibuf-tail stream) count)
667 count))
669 ;;;; utility functions (misc routines, etc)
671 ;;; Fill in the various routine slots for the given type. INPUT-P and
672 ;;; OUTPUT-P indicate what slots to fill. The buffering slot must be
673 ;;; set prior to calling this routine.
674 (defun set-fd-stream-routines (fd-stream type input-p output-p buffer-p)
675 (let ((target-type (case type
676 ((:default unsigned-byte)
677 '(unsigned-byte 8))
678 (signed-byte
679 '(signed-byte 8))
681 type)))
682 (input-type nil)
683 (output-type nil)
684 (input-size nil)
685 (output-size nil))
687 (when (fd-stream-obuf-sap fd-stream)
688 (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
689 (setf (fd-stream-obuf-sap fd-stream) nil))
690 (when (fd-stream-ibuf-sap fd-stream)
691 (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
692 (setf (fd-stream-ibuf-sap fd-stream) nil))
694 (when input-p
695 (multiple-value-bind (routine type size)
696 (pick-input-routine target-type)
697 (unless routine
698 (error "could not find any input routine for ~S" target-type))
699 (setf (fd-stream-ibuf-sap fd-stream) (next-available-buffer))
700 (setf (fd-stream-ibuf-length fd-stream) bytes-per-buffer)
701 (setf (fd-stream-ibuf-tail fd-stream) 0)
702 (if (subtypep type 'character)
703 (setf (fd-stream-in fd-stream) routine
704 (fd-stream-bin fd-stream) #'ill-bin)
705 (setf (fd-stream-in fd-stream) #'ill-in
706 (fd-stream-bin fd-stream) routine))
707 (when (eql size 1)
708 (setf (fd-stream-n-bin fd-stream) #'fd-stream-read-n-bytes)
709 (when (and buffer-p
710 ;; We only create this buffer for streams of type
711 ;; (unsigned-byte 8). Because there's no buffer, the
712 ;; other element-types will dispatch to the appropriate
713 ;; input (output) routine in fast-read-byte.
714 (equal target-type '(unsigned-byte 8))
715 #+nil
716 (or (eq type 'unsigned-byte)
717 (eq type :default)))
718 (setf (ansi-stream-in-buffer fd-stream)
719 (make-array +ansi-stream-in-buffer-length+
720 :element-type '(unsigned-byte 8)))))
721 (setf input-size size)
722 (setf input-type type)))
724 (when output-p
725 (multiple-value-bind (routine type size)
726 (pick-output-routine target-type (fd-stream-buffering fd-stream))
727 (unless routine
728 (error "could not find any output routine for ~S buffered ~S"
729 (fd-stream-buffering fd-stream)
730 target-type))
731 (setf (fd-stream-obuf-sap fd-stream) (next-available-buffer))
732 (setf (fd-stream-obuf-length fd-stream) bytes-per-buffer)
733 (setf (fd-stream-obuf-tail fd-stream) 0)
734 (if (subtypep type 'character)
735 (setf (fd-stream-out fd-stream) routine
736 (fd-stream-bout fd-stream) #'ill-bout)
737 (setf (fd-stream-out fd-stream)
738 (or (if (eql size 1)
739 (pick-output-routine 'base-char
740 (fd-stream-buffering fd-stream)))
741 #'ill-out)
742 (fd-stream-bout fd-stream) routine))
743 (setf (fd-stream-sout fd-stream)
744 (if (eql size 1) #'fd-sout #'ill-out))
745 (setf (fd-stream-char-pos fd-stream) 0)
746 (setf output-size size)
747 (setf output-type type)))
749 (when (and input-size output-size
750 (not (eq input-size output-size)))
751 (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
752 input-type input-size
753 output-type output-size))
754 (setf (fd-stream-element-size fd-stream)
755 (or input-size output-size))
757 (setf (fd-stream-element-type fd-stream)
758 (cond ((equal input-type output-type)
759 input-type)
760 ((null output-type)
761 input-type)
762 ((null input-type)
763 output-type)
764 ((subtypep input-type output-type)
765 input-type)
766 ((subtypep output-type input-type)
767 output-type)
769 (error "Input type (~S) and output type (~S) are unrelated?"
770 input-type
771 output-type))))))
773 ;;; Handle miscellaneous operations on FD-STREAM.
774 (defun fd-stream-misc-routine (fd-stream operation &optional arg1 arg2)
775 (declare (ignore arg2))
776 (case operation
777 (:listen
778 (or (not (eql (fd-stream-ibuf-head fd-stream)
779 (fd-stream-ibuf-tail fd-stream)))
780 (fd-stream-listen fd-stream)
781 (setf (fd-stream-listen fd-stream)
782 (eql (sb!alien:with-alien ((read-fds (sb!alien:struct
783 sb!unix:fd-set)))
784 (sb!unix:fd-zero read-fds)
785 (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
786 (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
787 (sb!alien:addr read-fds)
788 nil nil 0 0))
789 1))))
790 (:unread
791 (setf (fd-stream-unread fd-stream) arg1)
792 (setf (fd-stream-listen fd-stream) t))
793 (:close
794 (cond (arg1
795 ;; We got us an abort on our hands.
796 (when (fd-stream-handler fd-stream)
797 (sb!sys:remove-fd-handler (fd-stream-handler fd-stream))
798 (setf (fd-stream-handler fd-stream) nil))
799 (when (and (fd-stream-file fd-stream)
800 (fd-stream-obuf-sap fd-stream))
801 ;; We can't do anything unless we know what file were
802 ;; dealing with, and we don't want to do anything
803 ;; strange unless we were writing to the file.
804 (if (fd-stream-original fd-stream)
805 ;; We have a handle on the original, just revert.
806 (multiple-value-bind (okay err)
807 (sb!unix:unix-rename (fd-stream-original fd-stream)
808 (fd-stream-file fd-stream))
809 (unless okay
810 (simple-stream-perror
811 "couldn't restore ~S to its original contents"
812 fd-stream
813 err)))
814 ;; We can't restore the original, so nuke that puppy.
815 (multiple-value-bind (okay err)
816 (sb!unix:unix-unlink (fd-stream-file fd-stream))
817 (unless okay
818 (error 'simple-file-error
819 :pathname (fd-stream-file fd-stream)
820 :format-control
821 "~@<couldn't remove ~S: ~2I~_~A~:>"
822 :format-arguments (list (fd-stream-file fd-stream)
823 (strerror err))))))))
825 (fd-stream-misc-routine fd-stream :finish-output)
826 (when (and (fd-stream-original fd-stream)
827 (fd-stream-delete-original fd-stream))
828 (multiple-value-bind (okay err)
829 (sb!unix:unix-unlink (fd-stream-original fd-stream))
830 (unless okay
831 (error 'simple-file-error
832 :pathname (fd-stream-original fd-stream)
833 :format-control
834 "~@<couldn't delete ~S during close of ~S: ~
835 ~2I~_~A~:>"
836 :format-arguments
837 (list (fd-stream-original fd-stream)
838 fd-stream
839 (strerror err))))))))
840 (when (fboundp 'cancel-finalization)
841 (cancel-finalization fd-stream))
842 (sb!unix:unix-close (fd-stream-fd fd-stream))
843 (when (fd-stream-obuf-sap fd-stream)
844 (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
845 (setf (fd-stream-obuf-sap fd-stream) nil))
846 (when (fd-stream-ibuf-sap fd-stream)
847 (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
848 (setf (fd-stream-ibuf-sap fd-stream) nil))
849 (sb!impl::set-closed-flame fd-stream))
850 (:clear-input
851 (setf (fd-stream-unread fd-stream) nil)
852 (setf (fd-stream-ibuf-head fd-stream) 0)
853 (setf (fd-stream-ibuf-tail fd-stream) 0)
854 (catch 'eof-input-catcher
855 (loop
856 (let ((count (sb!alien:with-alien ((read-fds (sb!alien:struct
857 sb!unix:fd-set)))
858 (sb!unix:fd-zero read-fds)
859 (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
860 (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
861 (sb!alien:addr read-fds)
865 0))))
866 (cond ((eql count 1)
867 (frob-input fd-stream)
868 (setf (fd-stream-ibuf-head fd-stream) 0)
869 (setf (fd-stream-ibuf-tail fd-stream) 0))
871 (return t)))))))
872 (:force-output
873 (flush-output-buffer fd-stream))
874 (:finish-output
875 (flush-output-buffer fd-stream)
876 (do ()
877 ((null (fd-stream-output-later fd-stream)))
878 (sb!sys:serve-all-events)))
879 (:element-type
880 (fd-stream-element-type fd-stream))
881 (:interactive-p
882 (= 1 (the (member 0 1)
883 (sb!unix:unix-isatty (fd-stream-fd fd-stream)))))
884 (:line-length
886 (:charpos
887 (fd-stream-char-pos fd-stream))
888 (:file-length
889 (unless (fd-stream-file fd-stream)
890 ;; This is a TYPE-ERROR because ANSI's species FILE-LENGTH
891 ;; "should signal an error of type TYPE-ERROR if stream is not
892 ;; a stream associated with a file". Too bad there's no very
893 ;; appropriate value for the EXPECTED-TYPE slot..
894 (error 'simple-type-error
895 :datum fd-stream
896 :expected-type 'file-stream
897 :format-control "~S is not a stream associated with a file."
898 :format-arguments (list fd-stream)))
899 (multiple-value-bind (okay dev ino mode nlink uid gid rdev size
900 atime mtime ctime blksize blocks)
901 (sb!unix:unix-fstat (fd-stream-fd fd-stream))
902 (declare (ignore ino nlink uid gid rdev
903 atime mtime ctime blksize blocks))
904 (unless okay
905 (simple-stream-perror "failed Unix fstat(2) on ~S" fd-stream dev))
906 (if (zerop mode)
908 (truncate size (fd-stream-element-size fd-stream)))))
909 (:file-position
910 (fd-stream-file-position fd-stream arg1))))
912 (defun fd-stream-file-position (stream &optional newpos)
913 (declare (type file-stream stream)
914 (type (or (alien sb!unix:off-t) (member nil :start :end)) newpos))
915 (if (null newpos)
916 (sb!sys:without-interrupts
917 ;; First, find the position of the UNIX file descriptor in the file.
918 (multiple-value-bind (posn errno)
919 (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr)
920 (declare (type (or (alien sb!unix:off-t) null) posn))
921 (cond ((integerp posn)
922 ;; Adjust for buffered output: If there is any output
923 ;; buffered, the *real* file position will be larger
924 ;; than reported by lseek() because lseek() obviously
925 ;; cannot take into account output we have not sent
926 ;; yet.
927 (dolist (later (fd-stream-output-later stream))
928 (incf posn (- (caddr later)
929 (cadr later))))
930 (incf posn (fd-stream-obuf-tail stream))
931 ;; Adjust for unread input: If there is any input
932 ;; read from UNIX but not supplied to the user of the
933 ;; stream, the *real* file position will smaller than
934 ;; reported, because we want to look like the unread
935 ;; stuff is still available.
936 (decf posn (- (fd-stream-ibuf-tail stream)
937 (fd-stream-ibuf-head stream)))
938 (when (fd-stream-unread stream)
939 (decf posn))
940 ;; Divide bytes by element size.
941 (truncate posn (fd-stream-element-size stream)))
942 ((eq errno sb!unix:espipe)
943 nil)
945 (sb!sys:with-interrupts
946 (simple-stream-perror "failure in Unix lseek() on ~S"
947 stream
948 errno))))))
949 (let ((offset 0) origin)
950 (declare (type (alien sb!unix:off-t) offset))
951 ;; Make sure we don't have any output pending, because if we
952 ;; move the file pointer before writing this stuff, it will be
953 ;; written in the wrong location.
954 (flush-output-buffer stream)
955 (do ()
956 ((null (fd-stream-output-later stream)))
957 (sb!sys:serve-all-events))
958 ;; Clear out any pending input to force the next read to go to
959 ;; the disk.
960 (setf (fd-stream-unread stream) nil)
961 (setf (fd-stream-ibuf-head stream) 0)
962 (setf (fd-stream-ibuf-tail stream) 0)
963 ;; Trash cached value for listen, so that we check next time.
964 (setf (fd-stream-listen stream) nil)
965 ;; Now move it.
966 (cond ((eq newpos :start)
967 (setf offset 0 origin sb!unix:l_set))
968 ((eq newpos :end)
969 (setf offset 0 origin sb!unix:l_xtnd))
970 ((typep newpos '(alien sb!unix:off-t))
971 (setf offset (* newpos (fd-stream-element-size stream))
972 origin sb!unix:l_set))
974 (error "invalid position given to FILE-POSITION: ~S" newpos)))
975 (multiple-value-bind (posn errno)
976 (sb!unix:unix-lseek (fd-stream-fd stream) offset origin)
977 (cond ((typep posn '(alien sb!unix:off-t))
979 ((eq errno sb!unix:espipe)
980 nil)
982 (simple-stream-perror "error in Unix lseek() on ~S"
983 stream
984 errno)))))))
986 ;;;; creation routines (MAKE-FD-STREAM and OPEN)
988 ;;; Create a stream for the given Unix file descriptor.
990 ;;; If INPUT is non-NIL, allow input operations. If OUTPUT is non-nil,
991 ;;; allow output operations. If neither INPUT nor OUTPUT is specified,
992 ;;; default to allowing input.
994 ;;; ELEMENT-TYPE indicates the element type to use (as for OPEN).
996 ;;; BUFFERING indicates the kind of buffering to use.
998 ;;; TIMEOUT (if true) is the number of seconds to wait for input. If
999 ;;; NIL (the default), then wait forever. When we time out, we signal
1000 ;;; IO-TIMEOUT.
1002 ;;; FILE is the name of the file (will be returned by PATHNAME).
1004 ;;; NAME is used to identify the stream when printed.
1005 (defun make-fd-stream (fd
1006 &key
1007 (input nil input-p)
1008 (output nil output-p)
1009 (element-type 'base-char)
1010 (buffering :full)
1011 timeout
1012 file
1013 original
1014 delete-original
1015 pathname
1016 input-buffer-p
1017 (name (if file
1018 (format nil "file ~S" file)
1019 (format nil "descriptor ~W" fd)))
1020 auto-close)
1021 (declare (type index fd) (type (or index null) timeout)
1022 (type (member :none :line :full) buffering))
1023 (cond ((not (or input-p output-p))
1024 (setf input t))
1025 ((not (or input output))
1026 (error "File descriptor must be opened either for input or output.")))
1027 (let ((stream (%make-fd-stream :fd fd
1028 :name name
1029 :file file
1030 :original original
1031 :delete-original delete-original
1032 :pathname pathname
1033 :buffering buffering
1034 :timeout timeout)))
1035 (set-fd-stream-routines stream element-type input output input-buffer-p)
1036 (when (and auto-close (fboundp 'finalize))
1037 (finalize stream
1038 (lambda ()
1039 (sb!unix:unix-close fd)
1040 #!+sb-show
1041 (format *terminal-io* "** closed file descriptor ~W **~%"
1042 fd))))
1043 stream))
1045 ;;; Pick a name to use for the backup file for the :IF-EXISTS
1046 ;;; :RENAME-AND-DELETE and :RENAME options.
1047 (defun pick-backup-name (name)
1048 (declare (type simple-base-string name))
1049 (concatenate 'simple-base-string name ".bak"))
1051 ;;; Ensure that the given arg is one of the given list of valid
1052 ;;; things. Allow the user to fix any problems.
1053 (defun ensure-one-of (item list what)
1054 (unless (member item list)
1055 (error 'simple-type-error
1056 :datum item
1057 :expected-type `(member ,@list)
1058 :format-control "~@<~S is ~_invalid for ~S; ~_need one of~{ ~S~}~:>"
1059 :format-arguments (list item what list))))
1061 ;;; Rename NAMESTRING to ORIGINAL. First, check whether we have write
1062 ;;; access, since we don't want to trash unwritable files even if we
1063 ;;; technically can. We return true if we succeed in renaming.
1064 (defun rename-the-old-one (namestring original)
1065 (unless (sb!unix:unix-access namestring sb!unix:w_ok)
1066 (error "~@<The file ~2I~_~S ~I~_is not writable.~:>" namestring))
1067 (multiple-value-bind (okay err) (sb!unix:unix-rename namestring original)
1068 (if okay
1070 (error 'simple-file-error
1071 :pathname namestring
1072 :format-control
1073 "~@<couldn't rename ~2I~_~S ~I~_to ~2I~_~S: ~4I~_~A~:>"
1074 :format-arguments (list namestring original (strerror err))))))
1076 (defun open (filename
1077 &key
1078 (direction :input)
1079 (element-type 'base-char)
1080 (if-exists nil if-exists-given)
1081 (if-does-not-exist nil if-does-not-exist-given)
1082 (external-format :default)
1083 &aux ; Squelch assignment warning.
1084 (direction direction)
1085 (if-does-not-exist if-does-not-exist)
1086 (if-exists if-exists))
1087 #!+sb-doc
1088 "Return a stream which reads from or writes to FILENAME.
1089 Defined keywords:
1090 :DIRECTION - one of :INPUT, :OUTPUT, :IO, or :PROBE
1091 :ELEMENT-TYPE - the type of object to read or write, default BASE-CHAR
1092 :IF-EXISTS - one of :ERROR, :NEW-VERSION, :RENAME, :RENAME-AND-DELETE,
1093 :OVERWRITE, :APPEND, :SUPERSEDE or NIL
1094 :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or NIL
1095 See the manual for details."
1097 ;; Calculate useful stuff.
1098 (multiple-value-bind (input output mask)
1099 (case direction
1100 (:input (values t nil sb!unix:o_rdonly))
1101 (:output (values nil t sb!unix:o_wronly))
1102 (:io (values t t sb!unix:o_rdwr))
1103 (:probe (values t nil sb!unix:o_rdonly)))
1104 (declare (type index mask))
1105 (let* ((pathname (merge-pathnames filename))
1106 (namestring
1107 (cond ((unix-namestring pathname input))
1108 ((and input (eq if-does-not-exist :create))
1109 (unix-namestring pathname nil))
1110 ((and (eq direction :io) (not if-does-not-exist-given))
1111 (unix-namestring pathname nil)))))
1112 ;; Process if-exists argument if we are doing any output.
1113 (cond (output
1114 (unless if-exists-given
1115 (setf if-exists
1116 (if (eq (pathname-version pathname) :newest)
1117 :new-version
1118 :error)))
1119 (ensure-one-of if-exists
1120 '(:error :new-version :rename
1121 :rename-and-delete :overwrite
1122 :append :supersede nil)
1123 :if-exists)
1124 (case if-exists
1125 ((:new-version :error nil)
1126 (setf mask (logior mask sb!unix:o_excl)))
1127 ((:rename :rename-and-delete)
1128 (setf mask (logior mask sb!unix:o_creat)))
1129 ((:supersede)
1130 (setf mask (logior mask sb!unix:o_trunc)))
1131 (:append
1132 (setf mask (logior mask sb!unix:o_append)))))
1134 (setf if-exists :ignore-this-arg)))
1136 (unless if-does-not-exist-given
1137 (setf if-does-not-exist
1138 (cond ((eq direction :input) :error)
1139 ((and output
1140 (member if-exists '(:overwrite :append)))
1141 :error)
1142 ((eq direction :probe)
1143 nil)
1145 :create))))
1146 (ensure-one-of if-does-not-exist
1147 '(:error :create nil)
1148 :if-does-not-exist)
1149 (if (eq if-does-not-exist :create)
1150 (setf mask (logior mask sb!unix:o_creat)))
1152 (let ((original (if (member if-exists
1153 '(:rename :rename-and-delete))
1154 (pick-backup-name namestring)))
1155 (delete-original (eq if-exists :rename-and-delete))
1156 (mode #o666))
1157 (when original
1158 ;; We are doing a :RENAME or :RENAME-AND-DELETE. Determine
1159 ;; whether the file already exists, make sure the original
1160 ;; file is not a directory, and keep the mode.
1161 (let ((exists
1162 (and namestring
1163 (multiple-value-bind (okay err/dev inode orig-mode)
1164 (sb!unix:unix-stat namestring)
1165 (declare (ignore inode)
1166 (type (or index null) orig-mode))
1167 (cond
1168 (okay
1169 (when (and output (= (logand orig-mode #o170000)
1170 #o40000))
1171 (error 'simple-file-error
1172 :pathname namestring
1173 :format-control
1174 "can't open ~S for output: is a directory"
1175 :format-arguments (list namestring)))
1176 (setf mode (logand orig-mode #o777))
1178 ((eql err/dev sb!unix:enoent)
1179 nil)
1181 (simple-file-perror "can't find ~S"
1182 namestring
1183 err/dev)))))))
1184 (unless (and exists
1185 (rename-the-old-one namestring original))
1186 (setf original nil)
1187 (setf delete-original nil)
1188 ;; In order to use :SUPERSEDE instead, we have to make
1189 ;; sure SB!UNIX:O_CREAT corresponds to
1190 ;; IF-DOES-NOT-EXIST. SB!UNIX:O_CREAT was set before
1191 ;; because of IF-EXISTS being :RENAME.
1192 (unless (eq if-does-not-exist :create)
1193 (setf mask
1194 (logior (logandc2 mask sb!unix:o_creat)
1195 sb!unix:o_trunc)))
1196 (setf if-exists :supersede))))
1198 ;; Now we can try the actual Unix open(2).
1199 (multiple-value-bind (fd errno)
1200 (if namestring
1201 (sb!unix:unix-open namestring mask mode)
1202 (values nil sb!unix:enoent))
1203 (labels ((open-error (format-control &rest format-arguments)
1204 (error 'simple-file-error
1205 :pathname pathname
1206 :format-control format-control
1207 :format-arguments format-arguments))
1208 (vanilla-open-error ()
1209 (simple-file-perror "error opening ~S" pathname errno)))
1210 (cond ((numberp fd)
1211 (case direction
1212 ((:input :output :io)
1213 (make-fd-stream fd
1214 :input input
1215 :output output
1216 :element-type element-type
1217 :file namestring
1218 :original original
1219 :delete-original delete-original
1220 :pathname pathname
1221 :input-buffer-p t
1222 :auto-close t))
1223 (:probe
1224 (let ((stream
1225 (%make-fd-stream :name namestring
1226 :fd fd
1227 :pathname pathname
1228 :element-type element-type)))
1229 (close stream)
1230 stream))))
1231 ((eql errno sb!unix:enoent)
1232 (case if-does-not-exist
1233 (:error (vanilla-open-error))
1234 (:create
1235 (open-error "~@<The path ~2I~_~S ~I~_does not exist.~:>"
1236 pathname))
1237 (t nil)))
1238 ((and (eql errno sb!unix:eexist) (null if-exists))
1239 nil)
1241 (vanilla-open-error)))))))))
1243 ;;;; initialization
1245 ;;; the stream connected to the controlling terminal, or NIL if there is none
1246 (defvar *tty*)
1248 ;;; the stream connected to the standard input (file descriptor 0)
1249 (defvar *stdin*)
1251 ;;; the stream connected to the standard output (file descriptor 1)
1252 (defvar *stdout*)
1254 ;;; the stream connected to the standard error output (file descriptor 2)
1255 (defvar *stderr*)
1257 ;;; This is called when the cold load is first started up, and may also
1258 ;;; be called in an attempt to recover from nested errors.
1259 (defun stream-cold-init-or-reset ()
1260 (stream-reinit)
1261 (setf *terminal-io* (make-synonym-stream '*tty*))
1262 (setf *standard-output* (make-synonym-stream '*stdout*))
1263 (setf *standard-input* (make-synonym-stream '*stdin*))
1264 (setf *error-output* (make-synonym-stream '*stderr*))
1265 (setf *query-io* (make-synonym-stream '*terminal-io*))
1266 (setf *debug-io* *query-io*)
1267 (setf *trace-output* *standard-output*)
1268 (values))
1270 ;;; This is called whenever a saved core is restarted.
1271 (defun stream-reinit ()
1272 (setf *available-buffers* nil)
1273 (setf *stdin*
1274 (make-fd-stream 0 :name "standard input" :input t :buffering :line))
1275 (setf *stdout*
1276 (make-fd-stream 1 :name "standard output" :output t :buffering :line))
1277 (setf *stderr*
1278 (make-fd-stream 2 :name "standard error" :output t :buffering :line))
1279 (let ((tty (sb!unix:unix-open "/dev/tty" sb!unix:o_rdwr #o666)))
1280 (if tty
1281 (setf *tty*
1282 (make-fd-stream tty
1283 :name "the terminal"
1284 :input t
1285 :output t
1286 :buffering :line
1287 :auto-close t))
1288 (setf *tty* (make-two-way-stream *stdin* *stdout*))))
1289 (values))
1291 ;;;; miscellany
1293 ;;; the Unix way to beep
1294 (defun beep (stream)
1295 (write-char (code-char bell-char-code) stream)
1296 (finish-output stream))
1298 ;;; This is kind of like FILE-POSITION, but is an internal hack used
1299 ;;; by the filesys stuff to get and set the file name.
1301 ;;; FIXME: misleading name, screwy interface
1302 (defun file-name (stream &optional new-name)
1303 (when (typep stream 'file-stream)
1304 (cond (new-name
1305 (setf (fd-stream-pathname stream) new-name)
1306 (setf (fd-stream-file stream)
1307 (unix-namestring new-name nil))
1310 (fd-stream-pathname stream)))))
1312 ;;;; international character support (which is trivial for our simple
1313 ;;;; character sets)
1315 ;;;; (Those who do Lisp only in English might not remember that ANSI
1316 ;;;; requires these functions to be exported from package
1317 ;;;; COMMON-LISP.)
1319 (defun file-string-length (stream object)
1320 (declare (type (or string character) object) (type file-stream stream))
1321 #!+sb-doc
1322 "Return the delta in STREAM's FILE-POSITION that would be caused by writing
1323 OBJECT to STREAM. Non-trivial only in implementations that support
1324 international character sets."
1325 (declare (ignore stream))
1326 (etypecase object
1327 (character 1)
1328 (string (length object))))
1330 (defun stream-external-format (stream)
1331 (declare (type file-stream stream) (ignore stream))
1332 #!+sb-doc
1333 "Return :DEFAULT."
1334 :default)