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")
16 ;;;; Streams hold BUFFER objects, which contain a SAP, size of the
17 ;;;; memory area the SAP stands for (LENGTH bytes), and HEAD and TAIL
18 ;;;; indexes which delimit the "valid", or "active" area of the
19 ;;;; memory. HEAD is inclusive, TAIL is exclusive.
21 ;;;; Buffers get allocated lazily, and are recycled by returning them
22 ;;;; to the *AVAILABLE-BUFFERS* list. Every buffer has it's own
23 ;;;; finalizer, to take care of releasing the SAP memory when a stream
24 ;;;; is not properly closed.
26 ;;;; The code aims to provide a limited form of thread and interrupt
27 ;;;; safety: parallel writes and reads may lose output or input, cause
28 ;;;; interleaved IO, etc -- but they should not corrupt memory. The
29 ;;;; key to doing this is to read buffer state once, and update the
30 ;;;; state based on the read state:
32 ;;;; (let ((tail (buffer-tail buffer)))
34 ;;;; (setf (buffer-tail buffer) (+ tail n)))
38 ;;;; (let ((tail (buffer-tail buffer)))
40 ;;;; (incf (buffer-tail buffer) n))
43 (declaim (inline buffer-sap buffer-length buffer-head buffer-tail
44 (setf buffer-head
) (setf buffer-tail
)))
45 (defstruct (buffer (:constructor %make-buffer
(sap length
)))
46 (sap (missing-arg) :type system-area-pointer
:read-only t
)
47 (length (missing-arg) :type index
:read-only t
)
51 (defvar *available-buffers
* ()
53 "List of available buffers.")
55 (defvar *available-buffers-spinlock
* (sb!thread
::make-spinlock
56 :name
"lock for *AVAILABLE-BUFFERS*")
58 "Mutex for access to *AVAILABLE-BUFFERS*.")
60 (defmacro with-available-buffers-lock
((&optional
) &body body
)
61 ;; CALL-WITH-SYSTEM-SPINLOCK because
63 ;; 1. streams are low-level enough to be async signal safe, and in
64 ;; particular a C-c that brings up the debugger while holding the
65 ;; mutex would lose badly
67 ;; 2. this can potentially be a fairly busy (but also probably
68 ;; uncontended) lock, so we don't want to pay the syscall per
69 ;; release -- hence a spinlock.
71 ;; ...again, once we have smarted locks the spinlock here can become
73 `(sb!thread
::call-with-system-spinlock
(lambda () ,@body
)
74 *available-buffers-spinlock
*))
76 (defconstant +bytes-per-buffer
+ (* 4 1024)
78 "Default number of bytes per buffer.")
80 (defun alloc-buffer (&optional
(size +bytes-per-buffer
+))
81 ;; Don't want to allocate & unwind before the finalizer is in place.
83 (let* ((sap (allocate-system-memory size
))
84 (buffer (%make-buffer sap size
)))
85 (when (zerop (sap-int sap
))
86 (error "Could not allocate ~D bytes for buffer." size
))
87 (finalize buffer
(lambda ()
88 (deallocate-system-memory sap size
))
93 ;; Don't go for the lock if there is nothing to be had -- sure,
94 ;; another thread might just release one before we get it, but that
95 ;; is not worth the cost of locking. Also release the lock before
96 ;; allocation, since it's going to take a while.
97 (if *available-buffers
*
98 (or (with-available-buffers-lock ()
99 (pop *available-buffers
*))
103 (declaim (inline reset-buffer
))
104 (defun reset-buffer (buffer)
105 (setf (buffer-head buffer
) 0
106 (buffer-tail buffer
) 0)
109 (defun release-buffer (buffer)
110 (reset-buffer buffer
)
111 (with-available-buffers-lock ()
112 (push buffer
*available-buffers
*)))
114 ;;; This is a separate buffer management function, as it wants to be
115 ;;; clever about locking -- grabbing the lock just once.
116 (defun release-fd-stream-buffers (fd-stream)
117 (let ((ibuf (fd-stream-ibuf fd-stream
))
118 (obuf (fd-stream-obuf fd-stream
))
119 (queue (loop for item in
(fd-stream-output-queue fd-stream
)
121 collect
(reset-buffer item
))))
123 (push (reset-buffer ibuf
) queue
))
125 (push (reset-buffer obuf
) queue
))
126 ;; ...so, anything found?
128 ;; detach from stream
129 (setf (fd-stream-ibuf fd-stream
) nil
130 (fd-stream-obuf fd-stream
) nil
131 (fd-stream-output-queue fd-stream
) nil
)
132 ;; splice to *available-buffers*
133 (with-available-buffers-lock ()
134 (setf *available-buffers
* (nconc queue
*available-buffers
*))))))
136 ;;;; the FD-STREAM structure
138 (defstruct (fd-stream
139 (:constructor %make-fd-stream
)
140 (:conc-name fd-stream-
)
141 (:predicate fd-stream-p
)
142 (:include ansi-stream
143 (misc #'fd-stream-misc-routine
))
146 ;; the name of this stream (should be deprecated: this slot's
147 ;; purpose is better served with PRINT-OBJECT methods).
149 ;; the file this stream is for (Deprecated: we now store the
150 ;; truename, rather than a string, in the TRUENAME slot. Nothing in
151 ;; SBCL should use this slot anymore; if you're looking at this
152 ;; because we broke your use of FD-STREAMs, you're probably doing
154 (file nil
:type null
:read-only t
)
156 ;; Deprecated. We don't use these anymore, and you shouldn't either.
157 (original nil
:type null
:read-only t
)
158 (delete-original nil
:type null
:read-only t
)
159 ;;; the number of bytes per element
160 (element-size 1 :type index
)
161 ;; the type of element being transfered
162 (element-type 'base-char
)
163 ;; the Unix file descriptor
165 ;; controls when the output buffer is flushed
166 (buffering :full
:type
(member :full
:line
:none
))
167 ;; controls whether the input buffer must be cleared before output
168 ;; (must be done for files, not for sockets, pipes and other data
169 ;; sources where input and output aren't related). non-NIL means
170 ;; don't clear input buffer.
172 ;; character position if known -- this may run into bignums, but
173 ;; we probably should flip it into null then for efficiency's sake...
174 (char-pos nil
:type
(or unsigned-byte null
))
175 ;; T if input is waiting on FD. :EOF if we hit EOF.
176 (listen nil
:type
(member nil t
:eof
))
180 (ibuf nil
:type
(or buffer null
))
183 (obuf nil
:type
(or buffer null
))
185 ;; output flushed, but not written due to non-blocking io?
188 ;; timeout specified for this stream as seconds or NIL if none
189 (timeout nil
:type
(or single-float null
))
191 ;; Defaulted pathname used to open this stream (returned by PATHNAME)
192 (pathname nil
:type
(or pathname null
))
193 (external-format :default
)
194 ;; fixed width, or function to call with a character
195 (char-size 1 :type
(or fixnum function
))
196 (output-bytes #'ill-out
:type function
)
197 ;; Pathname of the file actually associated with the stream (used by
199 (truename nil
:type
(or pathname null
))
200 ;; If it's built with :OPEN-LAZY-FILE-DISPOSITION, for openings that
201 ;; create fresh files, the altname is the truename the file will
202 ;; have after a non-aborting CLOSE; if it's built without
203 ;; :OPEN-LAZY-FILE-DISPOSITION, the altname is the intermediate name of
204 ;; the old file for openings that replace an existing file.
205 (altname nil
:type
(or pathname null
))
206 ;; Actions to take after closing the descriptor (mostly side effects
207 ;; on the file system). If it's NIL, no actions will be taken.
208 (after-close nil
:type
(or function null
))
210 (owner-pid (sb!unix
:unix-getpid
) :type
(or null integer
))
211 ; #!+win32-uses-file-handles
212 ;; Win32 socket handles need some extra metadata for event
214 ; (events nil :type (or nil fixnum))
217 (def!method print-object
((fd-stream fd-stream
) stream
)
218 (declare (type stream stream
))
219 (print-unreadable-object (fd-stream stream
:type t
:identity t
)
220 (cond ((fd-stream-truename fd-stream
)
221 (format stream
"for file ~A" (fd-stream-truename fd-stream
)))
222 ((fd-stream-name fd-stream
)
223 (format stream
"for ~S" (fd-stream-name fd-stream
)))
225 (format stream
"for descriptor ~D" (fd-stream-fd fd-stream
))))
226 (format stream
"~:[ (stream is closed)~;~]"
227 (open-stream-p fd-stream
))))
229 ;;;; OS file device wrapper functions. For now, only use the win32
230 ;;;; API in case :WIN32-USES-FILE-HANDLES is in the target features.
231 ;;;; These functions are meant to have the API that the SB-UNIX
232 ;;;; bindings do: returning a true value for success, NIL and an error
233 ;;;; code for failure. The success value might be meaningful, or
234 ;;;; might not (e.g., for OS-CLOSE). The error codes are
235 ;;;; platform-specific; the error signaling machinery
236 ;;;; (SIMPLE-STREAM-PERROR, SIMPLE-FILE-PERROR) are responsible for
237 ;;;; turning these codes into messages or types.
239 (defun os-read (device buffer length
)
240 #!-win32-uses-file-handles
241 (sb!unix
:unix-read device buffer length
)
242 #!+win32-uses-file-handles
243 (sb!win32
:read-file device buffer length
))
245 (defun os-write (device buffer offset count
)
246 #!-win32-uses-file-handles
247 (sb!unix
:unix-write device buffer offset count
)
248 #!+win32-uses-file-handles
249 (sb!win32
:write-file device buffer offset count
))
251 (defun os-close (device)
252 #!-win32-uses-file-handles
253 (sb!unix
:unix-close device
)
254 #!+win32-uses-file-handles
255 (sb!win32
:close-handle device
))
257 (defun os-seek (device position whence
)
258 "Reposition the file pointer for DEVICE using POSITION and
259 WHENCE. WHENCE must be one of :START, :END, or T (meaning
260 relative to the current position)."
261 #!-win32-uses-file-handles
262 (sb!unix
:unix-lseek device position
264 (:start sb
!unix
:l_set
)
266 (:end sb
!unix
:l_xtnd
)))
267 #!+win32-uses-file-handles
268 (sb!win32
:set-file-pointer
269 device
(ldb (byte 32 0) position
) (ldb (byte 32 32) position
)
271 (:start sb
!win32
:file_begin
)
272 (t sb
!win32
:file_current
)
273 (:end sb
!win32
:file_end
))))
275 (defun os-file-length (device)
276 #!-win32-uses-file-handles
277 ;; FIXME: the wrapped_stat structure should really die. In this
278 ;; case, replacing it with a function that took an fd and returned
279 ;; the size would suffice.
280 (nth-value 8 (sb!unix
:unix-fstat device
))
281 #!+win32-uses-file-handles
282 (sb!win32
:get-file-size device
))
284 ;;; In order to not go bonkers trying to make POSIX open(2) and Win32
285 ;;; CreateFile() look similar, we invent the following internal API:
286 ;;; we'll use a lightweight structure, OS-OPEN-ARGUMENTS, containing
287 ;;; everything to be passed to open() or CreateFile() other than the
288 ;;; filename. The constructor, MAKE-OS-OPEN-ARGUMENTS, takes keywords
289 ;;; and &ALLOW-OTHER-KEYS, so that we can call the constructor on
290 ;;; whatever arguments OPEN receives; and there's a merging operation
291 ;;; that produces a new OS-OPEN-ARGUMENTS structure using
292 ;;; component-wise replacement rules like a CLtL1ish MERGE-PATHNAMES.
293 ;;; (So to make the following idea work, NIL must /never/ be a
294 ;;; meaningful argument to an opening syscall.) For the most part,
295 ;;; this means that most of the code can pass an opaque thing down the
298 ;; FIXME, maybe: I tried having this be a MACROLET, but the compiler
299 ;; complained that the lexical environment was too hairy to define the
300 ;; DEFSTRUCT accessors inside the MACROLET. Shrug.
301 (defmacro define-unnamed-list-struct
(name (&rest slot-names
))
302 (let ((strict-constructor (read-from-string (format nil
"%MAKE-~A" name
)))
303 (loose-constructor (read-from-string (format nil
"MAKE-~A" name
))))
304 `(progn (defstruct (,name
(:type list
) (:constructor
,strict-constructor
))
306 (defun ,loose-constructor
307 (&key
,@slot-names
&allow-other-keys
)
308 (list ,@slot-names
)))))
310 (define-unnamed-list-struct os-open-arguments
311 #!-win32-uses-file-handles
313 #!+win32-uses-file-handles
314 (desired-access share-mode security-attributes creation-disposition
315 flags-and-attributes template-file
))
318 ;; Unlike *DEFAULT-PATHNAME-DEFAULTS*, this should not be rebound
319 ;; anyplace. Explanations of these defaults: on both Unix and
320 ;; Windows, the defaults will open a file for reading only, and won't
321 ;; create a file where one doesn't exist. The other defaults have to
322 ;; do with metadata on a newly created file: on Unix, we are maximally
323 ;; permissive (but remember the umask); on Windows, everything gets
324 ;; defaulted in the file system.
325 (defvar *default-os-open-arguments-defaults
*
326 #!-win32-uses-file-handles
327 (%make-os-open-arguments
:flags sb
!unix
:o_rdonly
:mode
#o666
)
328 #!+win32-uses-file-handles
329 (%make-os-open-arguments
:desired-access sb
!win32
:generic_read
331 :security-attributes
0
332 :creation-disposition sb
!win32
:open_existing
333 :flags-and-attributes
0
335 "Default arguments to the operating system's file opening operation.")
337 (defun merge-os-open-arguments
338 (args &optional
(defaults *default-os-open-arguments-defaults
*))
339 (assert (= (length args
) (length *default-os-open-arguments-defaults
*)))
340 (mapcar (lambda (x y
) (or x y
)) args defaults
))
342 (defun os-open (filename os-open-arguments
)
343 (let ((args (merge-os-open-arguments os-open-arguments
)))
344 #!-win32-uses-file-handles
345 (destructuring-bind (flags mode
) args
346 (sb!unix
:unix-open filename flags mode
))
347 #!+win32-uses-file-handles
349 (access sharemode attributes disposition flags template
) args
350 (sb!win32
:create-file
351 filename access sharemode attributes disposition flags template
))))
353 ;;;; CORE OUTPUT FUNCTIONS
355 ;;; Buffer the section of THING delimited by START and END by copying
356 ;;; to output buffer(s) of stream.
357 (defun buffer-output (stream thing start end
)
358 (declare (index start end
))
360 (error ":END before :START!"))
362 ;; Copy bytes from THING to buffers.
363 (flet ((copy-to-buffer (buffer tail count
)
364 (declare (buffer buffer
) (index tail count
))
366 (let ((sap (buffer-sap buffer
)))
369 (system-area-ub8-copy thing start sap tail count
))
370 ((simple-unboxed-array (*))
371 (copy-ub8-to-system-area thing start sap tail count
))))
372 ;; Not INCF! If another thread has moved tail from under
373 ;; us, we don't want to accidentally increment tail
374 ;; beyond buffer-length.
375 (setf (buffer-tail buffer
) (+ count tail
))
378 ;; First copy is special: the buffer may already contain
379 ;; something, or be even full.
380 (let* ((obuf (fd-stream-obuf stream
))
381 (tail (buffer-tail obuf
))
382 (space (- (buffer-length obuf
) tail
)))
384 (copy-to-buffer obuf tail
(min space
(- end start
)))
385 (go :more-output-p
)))
387 ;; Later copies should always have an empty buffer, since
388 ;; they are freshly flushed, but if another thread is
389 ;; stomping on the same buffer that might not be the case.
390 (let* ((obuf (flush-output-buffer stream
))
391 (tail (buffer-tail obuf
))
392 (space (- (buffer-length obuf
) tail
)))
393 (copy-to-buffer obuf tail
(min space
(- end start
))))
396 (go :flush-and-fill
))))))
398 ;;; Flush the current output buffer of the stream, ensuring that the
399 ;;; new buffer is empty. Returns (for convenience) the new output
400 ;;; buffer -- which may or may not be EQ to the old one. If the is no
401 ;;; queued output we try to write the buffer immediately -- otherwise
402 ;;; we queue it for later.
403 (defun flush-output-buffer (stream)
404 (let ((obuf (fd-stream-obuf stream
)))
406 (let ((head (buffer-head obuf
))
407 (tail (buffer-tail obuf
)))
408 (cond ((eql head tail
)
409 ;; Buffer is already empty -- just ensure that is is
410 ;; set to zero as well.
412 ((fd-stream-output-queue stream
)
413 ;; There is already stuff on the queue -- go directly
416 (%queue-and-replace-output-buffer stream
))
418 ;; Try a non-blocking write, queue whatever is left over.
420 (synchronize-stream-output stream
)
421 (let ((length (- tail head
)))
422 (multiple-value-bind (count errno
)
423 (os-write (fd-stream-fd stream
) (buffer-sap obuf
)
425 (cond ((eql count length
)
426 ;; Complete write -- we can use the same buffer.
429 ;; Partial write -- update buffer status and queue.
430 ;; Do not use INCF! Another thread might have moved
432 (setf (buffer-head obuf
) (+ count head
))
433 (%queue-and-replace-output-buffer stream
))
435 ((eql errno sb
!unix
:ewouldblock
)
437 (%queue-and-replace-output-buffer stream
))
439 (simple-stream-perror "Couldn't write to ~s"
440 stream errno
)))))))))))
442 ;;; Helper for FLUSH-OUTPUT-BUFFER -- returns the new buffer.
443 (defun %queue-and-replace-output-buffer
(stream)
444 (let ((queue (fd-stream-output-queue stream
))
445 (later (list (or (fd-stream-obuf stream
) (bug "Missing obuf."))))
447 ;; Important: before putting the buffer on queue, give the stream
448 ;; a new one. If we get an interrupt and unwind losing the buffer
449 ;; is relatively OK, but having the same buffer in two places
451 (setf (fd-stream-obuf stream
) new
)
455 (setf (fd-stream-output-queue stream
) later
)))
456 (unless (fd-stream-handler stream
)
457 (setf (fd-stream-handler stream
)
458 (add-fd-handler (fd-stream-fd stream
)
461 (declare (ignore fd
))
462 (write-output-from-queue stream
)))))
465 ;;; This is called by the FD-HANDLER for the stream when output is
467 (defun write-output-from-queue (stream)
468 (synchronize-stream-output stream
)
472 (let* ((buffer (pop (fd-stream-output-queue stream
)))
473 (head (buffer-head buffer
))
474 (length (- (buffer-tail buffer
) head
)))
475 (declare (index head length
))
477 (multiple-value-bind (count errno
)
478 (os-write (fd-stream-fd stream
) (buffer-sap buffer
) head length
)
479 (cond ((eql count length
)
480 ;; Complete write, see if we can do another right
481 ;; away, or remove the handler if we're done.
482 (release-buffer buffer
)
483 (cond ((fd-stream-output-queue stream
)
487 (let ((handler (fd-stream-handler stream
)))
489 (setf (fd-stream-handler stream
) nil
)
490 (remove-fd-handler handler
)))))
492 ;; Partial write. Update buffer status and requeue.
493 (aver (< count length
))
494 ;; Do not use INCF! Another thread might have moved head.
495 (setf (buffer-head buffer
) (+ head count
))
496 (push buffer
(fd-stream-output-queue stream
)))
498 ;; We tried to do multiple writes, and finally our
499 ;; luck ran out. Requeue.
500 (push buffer
(fd-stream-output-queue stream
)))
502 ;; Could not write on the first try at all!
504 (simple-stream-perror "Couldn't write to ~S." stream errno
)
506 (if (= errno sb
!unix
:ewouldblock
)
507 (bug "Unexpected blocking in WRITE-OUTPUT-FROM-QUEUE.")
508 (simple-stream-perror "Couldn't write to ~S"
512 ;;; Try to write THING directly to STREAM without buffering, if
513 ;;; possible. If direct write doesn't happen, buffer.
514 (defun write-or-buffer-output (stream thing start end
)
515 (declare (index start end
))
516 (cond ((fd-stream-output-queue stream
)
517 (buffer-output stream thing start end
))
519 (error ":END before :START!"))
521 (let ((length (- end start
)))
522 (synchronize-stream-output stream
)
523 (multiple-value-bind (count errno
)
524 (os-write (fd-stream-fd stream
) thing start length
)
525 (cond ((eql count length
)
526 ;; Complete write -- done!
529 (aver (< count length
))
530 ;; Partial write -- buffer the rest.
531 (buffer-output stream thing
(+ start count
) end
))
533 ;; Could not write -- buffer or error.
535 (simple-stream-perror "couldn't write to ~s" stream errno
)
537 (if (= errno sb
!unix
:ewouldblock
)
538 (buffer-output stream thing start end
)
539 (simple-stream-perror "couldn't write to ~s" stream errno
)))))))))
541 ;;; Deprecated -- can go away after 1.1 or so. Deprecated because
542 ;;; this is not something we want to export. Nikodemus thinks the
543 ;;; right thing is to support a low-level non-stream like IO layer,
544 ;;; akin to java.nio.
545 (defun output-raw-bytes (stream thing
&optional start end
)
546 (write-or-buffer-output stream thing
(or start
0) (or end
(length thing
))))
548 (define-compiler-macro output-raw-bytes
(stream thing
&optional start end
)
549 (deprecation-warning 'output-raw-bytes
)
550 (let ((x (gensym "THING")))
552 (write-or-buffer-output ,stream
,x
(or ,start
0) (or ,end
(length ,x
))))))
554 ;;;; output routines and related noise
556 (defvar *output-routines
* ()
558 "List of all available output routines. Each element is a list of the
559 element-type output, the kind of buffering, the function name, and the number
560 of bytes per element.")
562 ;;; common idioms for reporting low-level stream and file problems
563 (defun simple-stream-perror (note-format stream errno
)
564 (error 'simple-stream-error
566 :format-control
"~@<~?: ~2I~_~A~:>"
568 (list note-format
(list stream
)
569 #!+unix
(strerror errno
)
570 #!+win32
(sb!win32
:get-last-error-message errno
))))
572 (defun file-error-type (error-code)
574 (#!+unix
#.sb
!unix
:enoent
#!+win32
#.sb
!win32
:error_file_not_found
575 'file-does-not-exist
)
576 (#!+unix
#.sb
!unix
:eexist
577 ;; What's the difference between ERROR_FILE_EXISTS and
578 ;; ERROR_ALREADY_EXISTS? AFAICT, one hundred and three.
579 #!+win32
#.sb
!win32
:error_file_exists
580 #!+win32
#.sb
!win32
:error_already_exists
582 (otherwise 'simple-file-error
)))
584 (defun simple-file-perror (note-format pathname errno
)
585 (error (file-error-type errno
)
587 :format-control
"~@<~?: ~2I~_~A~:>"
589 (list note-format
(list pathname
)
590 #!+unix
(strerror errno
)
591 #!+win32
(sb!win32
:get-last-error-message errno
))))
593 (defun stream-decoding-error (stream octets
)
594 (error 'stream-decoding-error
596 ;; FIXME: dunno how to get at OCTETS currently, or even if
597 ;; that's the right thing to report.
599 (defun stream-encoding-error (stream code
)
600 (error 'stream-encoding-error
604 (defun c-string-encoding-error (external-format code
)
605 (error 'c-string-encoding-error
606 :external-format external-format
609 (defun c-string-decoding-error (external-format octets
)
610 (error 'c-string-decoding-error
611 :external-format external-format
614 ;;; Returning true goes into end of file handling, false will enter another
615 ;;; round of input buffer filling followed by re-entering character decode.
616 (defun stream-decoding-error-and-handle (stream octet-count
)
618 (stream-decoding-error stream
619 (let* ((buffer (fd-stream-ibuf stream
))
620 (sap (buffer-sap buffer
))
621 (head (buffer-head buffer
)))
622 (loop for i from
0 below octet-count
623 collect
(sap-ref-8 sap
(+ head i
)))))
625 :report
(lambda (stream)
627 "~@<Attempt to resync the stream at a character ~
628 character boundary and continue.~@:>"))
629 (fd-stream-resync stream
)
631 (force-end-of-file ()
632 :report
(lambda (stream)
633 (format stream
"~@<Force an end of file.~@:>"))
636 (defun stream-encoding-error-and-handle (stream code
)
638 (stream-encoding-error stream code
)
640 :report
(lambda (stream)
641 (format stream
"~@<Skip output of this character.~@:>"))
642 (throw 'output-nothing nil
))))
644 (defun external-format-encoding-error (stream code
)
646 (stream-encoding-error-and-handle stream code
)
647 (c-string-encoding-error stream code
)))
649 (defun external-format-decoding-error (stream octet-count
)
651 (stream-decoding-error stream octet-count
)
652 (c-string-decoding-error stream octet-count
)))
654 (defun synchronize-stream-output (stream)
655 ;; If we're reading and writing on the same file, flush buffered
656 ;; input and rewind file position accordingly.
657 (unless (fd-stream-dual-channel-p stream
)
658 (let ((adjust (nth-value 1 (flush-input-buffer stream
))))
659 (unless (eql 0 adjust
)
660 (os-seek (fd-stream-fd stream
) (- adjust
) t
)))))
662 (defun fd-stream-output-finished-p (stream)
663 (let ((obuf (fd-stream-obuf stream
)))
665 (and (zerop (buffer-tail obuf
))
666 (not (fd-stream-output-queue stream
))))))
668 (defmacro output-wrapper
/variable-width
((stream size buffering restart
)
670 (let ((stream-var (gensym "STREAM")))
671 `(let* ((,stream-var
,stream
)
672 (obuf (fd-stream-obuf ,stream-var
))
673 (tail (buffer-tail obuf
))
675 ,(unless (eq (car buffering
) :none
)
676 `(when (<= (buffer-length obuf
) (+ tail size
))
677 (setf obuf
(flush-output-buffer ,stream-var
)
678 tail
(buffer-tail obuf
))))
679 ,(unless (eq (car buffering
) :none
)
680 ;; FIXME: Why this here? Doesn't seem necessary.
681 `(synchronize-stream-output ,stream-var
))
683 `(catch 'output-nothing
685 (setf (buffer-tail obuf
) (+ tail size
)))
688 (setf (buffer-tail obuf
) (+ tail size
))))
689 ,(ecase (car buffering
)
691 `(flush-output-buffer ,stream-var
))
693 `(when (eql byte
#\Newline
)
694 (flush-output-buffer ,stream-var
)))
698 (defmacro output-wrapper
((stream size buffering restart
) &body body
)
699 (let ((stream-var (gensym "STREAM")))
700 `(let* ((,stream-var
,stream
)
701 (obuf (fd-stream-obuf ,stream-var
))
702 (tail (buffer-tail obuf
)))
703 ,(unless (eq (car buffering
) :none
)
704 `(when (<= (buffer-length obuf
) (+ tail
,size
))
705 (setf obuf
(flush-output-buffer ,stream-var
)
706 tail
(buffer-tail obuf
))))
707 ;; FIXME: Why this here? Doesn't seem necessary.
708 ,(unless (eq (car buffering
) :none
)
709 `(synchronize-stream-output ,stream-var
))
711 `(catch 'output-nothing
713 (setf (buffer-tail obuf
) (+ tail
,size
)))
716 (setf (buffer-tail obuf
) (+ tail
,size
))))
717 ,(ecase (car buffering
)
719 `(flush-output-buffer ,stream-var
))
721 `(when (eql byte
#\Newline
)
722 (flush-output-buffer ,stream-var
)))
726 (defmacro def-output-routines
/variable-width
727 ((name-fmt size restart external-format
&rest bufferings
)
729 (declare (optimize (speed 1)))
734 (intern (format nil name-fmt
(string (car buffering
))))))
736 (defun ,function
(stream byte
)
737 (declare (ignorable byte
))
738 (output-wrapper/variable-width
(stream ,size
,buffering
,restart
)
740 (setf *output-routines
*
741 (nconc *output-routines
*
749 (cdr buffering
)))))))
752 ;;; Define output routines that output numbers SIZE bytes long for the
753 ;;; given bufferings. Use BODY to do the actual output.
754 (defmacro def-output-routines
((name-fmt size restart
&rest bufferings
)
756 (declare (optimize (speed 1)))
761 (intern (format nil name-fmt
(string (car buffering
))))))
763 (defun ,function
(stream byte
)
764 (output-wrapper (stream ,size
,buffering
,restart
)
766 (setf *output-routines
*
767 (nconc *output-routines
*
775 (cdr buffering
)))))))
778 ;;; FIXME: is this used anywhere any more?
779 (def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
785 (if (eql byte
#\Newline
)
786 (setf (fd-stream-char-pos stream
) 0)
787 (incf (fd-stream-char-pos stream
)))
788 (setf (sap-ref-8 (buffer-sap obuf
) tail
)
791 (def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
794 (:none
(unsigned-byte 8))
795 (:full
(unsigned-byte 8)))
796 (setf (sap-ref-8 (buffer-sap obuf
) tail
)
799 (def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
802 (:none
(signed-byte 8))
803 (:full
(signed-byte 8)))
804 (setf (signed-sap-ref-8 (buffer-sap obuf
) tail
)
807 (def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
810 (:none
(unsigned-byte 16))
811 (:full
(unsigned-byte 16)))
812 (setf (sap-ref-16 (buffer-sap obuf
) tail
)
815 (def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
818 (:none
(signed-byte 16))
819 (:full
(signed-byte 16)))
820 (setf (signed-sap-ref-16 (buffer-sap obuf
) tail
)
823 (def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
826 (:none
(unsigned-byte 32))
827 (:full
(unsigned-byte 32)))
828 (setf (sap-ref-32 (buffer-sap obuf
) tail
)
831 (def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
834 (:none
(signed-byte 32))
835 (:full
(signed-byte 32)))
836 (setf (signed-sap-ref-32 (buffer-sap obuf
) tail
)
839 #+#.
(cl:if
(cl:= sb
!vm
:n-word-bits
64) '(and) '(or))
841 (def-output-routines ("OUTPUT-UNSIGNED-LONG-LONG-~A-BUFFERED"
844 (:none
(unsigned-byte 64))
845 (:full
(unsigned-byte 64)))
846 (setf (sap-ref-64 (buffer-sap obuf
) tail
)
848 (def-output-routines ("OUTPUT-SIGNED-LONG-LONG-~A-BUFFERED"
851 (:none
(signed-byte 64))
852 (:full
(signed-byte 64)))
853 (setf (signed-sap-ref-64 (buffer-sap obuf
) tail
)
856 ;;; the routine to use to output a string. If the stream is
857 ;;; unbuffered, slam the string down the file descriptor, otherwise
858 ;;; use OUTPUT-RAW-BYTES to buffer the string. Update charpos by
859 ;;; checking to see where the last newline was.
860 (defun fd-sout (stream thing start end
)
861 (declare (type fd-stream stream
) (type string thing
))
862 (let ((start (or start
0))
863 (end (or end
(length (the vector thing
)))))
864 (declare (fixnum start end
))
866 (string-dispatch (simple-base-string
868 (simple-array character
(*))
871 (position #\newline thing
:from-end t
872 :start start
:end end
))))
873 (if (and (typep thing
'base-string
)
874 (eq (fd-stream-external-format stream
) :latin-1
))
875 (ecase (fd-stream-buffering stream
)
877 (buffer-output stream thing start end
))
879 (buffer-output stream thing start end
)
881 (flush-output-buffer stream
)))
883 (write-or-buffer-output stream thing start end
)))
884 (ecase (fd-stream-buffering stream
)
885 (:full
(funcall (fd-stream-output-bytes stream
)
886 stream thing nil start end
))
887 (:line
(funcall (fd-stream-output-bytes stream
)
888 stream thing last-newline start end
))
889 (:none
(funcall (fd-stream-output-bytes stream
)
890 stream thing t start end
))))
892 (setf (fd-stream-char-pos stream
) (- end last-newline
1))
893 (incf (fd-stream-char-pos stream
) (- end start
))))))
895 (defvar *external-formats
* ()
897 "List of all available external formats. Each element is a list of the
898 element-type, string input function name, character input function name,
899 and string output function name.")
901 (defun get-external-format (external-format)
902 (dolist (entry *external-formats
*)
903 (when (member external-format
(first entry
))
906 (defun get-external-format-function (external-format index
)
907 (let ((entry (get-external-format external-format
)))
908 (when entry
(nth index entry
))))
910 ;;; Find an output routine to use given the type and buffering. Return
911 ;;; as multiple values the routine, the real type transfered, and the
912 ;;; number of bytes per element.
913 (defun pick-output-routine (type buffering
&optional external-format
)
914 (when (subtypep type
'character
)
915 (let ((entry (get-external-format external-format
)))
917 (return-from pick-output-routine
918 (values (symbol-function (nth (ecase buffering
925 (symbol-function (fourth entry
))
926 (first (first entry
)))))))
927 (dolist (entry *output-routines
*)
928 (when (and (subtypep type
(first entry
))
929 (eq buffering
(second entry
))
930 (or (not (fifth entry
))
931 (eq external-format
(fifth entry
))))
932 (return-from pick-output-routine
933 (values (symbol-function (third entry
))
936 ;; KLUDGE: dealing with the buffering here leads to excessive code
939 ;; KLUDGE: also see comments in PICK-INPUT-ROUTINE
940 (loop for i from
40 by
8 to
1024 ; ARB (KLUDGE)
941 if
(subtypep type
`(unsigned-byte ,i
))
942 do
(return-from pick-output-routine
946 (lambda (stream byte
)
947 (output-wrapper (stream (/ i
8) (:none
) nil
)
948 (loop for j from
0 below
(/ i
8)
949 do
(setf (sap-ref-8 (buffer-sap obuf
)
951 (ldb (byte 8 (- i
8 (* j
8))) byte
))))))
953 (lambda (stream byte
)
954 (output-wrapper (stream (/ i
8) (:full
) nil
)
955 (loop for j from
0 below
(/ i
8)
956 do
(setf (sap-ref-8 (buffer-sap obuf
)
958 (ldb (byte 8 (- i
8 (* j
8))) byte
)))))))
961 (loop for i from
40 by
8 to
1024 ; ARB (KLUDGE)
962 if
(subtypep type
`(signed-byte ,i
))
963 do
(return-from pick-output-routine
967 (lambda (stream byte
)
968 (output-wrapper (stream (/ i
8) (:none
) nil
)
969 (loop for j from
0 below
(/ i
8)
970 do
(setf (sap-ref-8 (buffer-sap obuf
)
972 (ldb (byte 8 (- i
8 (* j
8))) byte
))))))
974 (lambda (stream byte
)
975 (output-wrapper (stream (/ i
8) (:full
) nil
)
976 (loop for j from
0 below
(/ i
8)
977 do
(setf (sap-ref-8 (buffer-sap obuf
)
979 (ldb (byte 8 (- i
8 (* j
8))) byte
)))))))
983 ;;;; input routines and related noise
985 ;;; a list of all available input routines. Each element is a list of
986 ;;; the element-type input, the function name, and the number of bytes
988 (defvar *input-routines
* ())
990 ;;; Return whether a primitive partial read operation on STREAM's FD
991 ;;; would (probably) block. Signal a `simple-stream-error' if the
992 ;;; system call implementing this operation fails.
994 ;;; It is "may" instead of "would" because "would" is not quite
995 ;;; correct on win32. However, none of the places that use it require
996 ;;; further assurance than "may" versus "will definitely not".
997 (defun sysread-may-block-p (stream)
998 #!+(and win32
(not win32-uses-file-handles
))
999 ;; This answers T at EOF on win32, I think.
1000 (not (sb!win32
:fd-listen
(fd-stream-fd stream
)))
1001 #!+(and win32 win32-uses-file-handles
)
1002 (not (sb!win32
:handle-listen
(fd-stream-fd stream
)))
1004 (sb!unix
:with-restarted-syscall
(count errno
)
1005 (sb!alien
:with-alien
((read-fds (sb!alien
:struct sb
!unix
:fd-set
)))
1006 (sb!unix
:fd-zero read-fds
)
1007 (sb!unix
:fd-set
(fd-stream-fd stream
) read-fds
)
1008 (sb!unix
:unix-fast-select
(1+ (fd-stream-fd stream
))
1009 (sb!alien
:addr read-fds
)
1015 (simple-stream-perror "couldn't check whether ~S is readable"
1019 ;;; If the read would block wait (using SERVE-EVENT) till input is available,
1020 ;;; then fill the input buffer, and return the number of bytes read. Throws
1021 ;;; to EOF-INPUT-CATCHER if the eof was reached.
1022 (defun refill-input-buffer (stream)
1023 (let ((fd (fd-stream-fd stream
))
1026 (declare (dynamic-extent fd errno count
))
1028 ;; Check for blocking input before touching the stream, as if
1029 ;; we happen to wait we are liable to be interrupted, and the
1030 ;; interrupt handler may use the same stream.
1031 (if (sysread-may-block-p stream
)
1032 (go :wait-for-input
)
1034 ;; These (:CLOSED-FLAME and :READ-ERROR) tags are here so what
1035 ;; we can signal errors outside the WITHOUT-INTERRUPTS.
1037 (closed-flame stream
)
1039 (simple-stream-perror "couldn't read from ~S" stream errno
)
1041 ;; This tag is here so we can unwind outside the WITHOUT-INTERRUPTS
1042 ;; to wait for input if read tells us EWOULDBLOCK.
1043 (unless (wait-until-fd-usable fd
:input
(fd-stream-timeout stream
))
1044 (signal-timeout 'io-timeout
:stream stream
:direction
:read
1045 :seconds
(fd-stream-timeout stream
)))
1047 ;; Since the read should not block, we'll disable the
1048 ;; interrupts here, so that we don't accidentally unwind and
1049 ;; leave the stream in an inconsistent state.
1051 ;; Execute the nlx outside without-interrupts to ensure the
1052 ;; resulting thunk is stack-allocatable.
1053 ((lambda (return-reason)
1054 (ecase return-reason
1055 ((nil)) ; fast path normal cases
1056 ((:wait-for-input
) (go :wait-for-input
))
1057 ((:closed-flame
) (go :closed-flame
))
1058 ((:read-error
) (go :read-error
))))
1060 ;; Check the buffer: if it is null, then someone has closed
1061 ;; the stream from underneath us. This is not ment to fix
1062 ;; multithreaded races, but to deal with interrupt handlers
1063 ;; closing the stream.
1066 (let* ((ibuf (or (fd-stream-ibuf stream
) (return :closed-flame
)))
1067 (sap (buffer-sap ibuf
))
1068 (length (buffer-length ibuf
))
1069 (head (buffer-head ibuf
))
1070 (tail (buffer-tail ibuf
)))
1071 (declare (index length head tail
)
1073 (unless (zerop head
)
1074 (cond ((eql head tail
)
1075 ;; Buffer is empty, but not at yet reset -- make it so.
1078 (reset-buffer ibuf
))
1080 ;; Buffer has things in it, but they are not at the
1081 ;; head -- move them there.
1082 (let ((n (- tail head
)))
1083 (system-area-ub8-copy sap head sap
0 n
)
1085 (buffer-head ibuf
) head
1087 (buffer-tail ibuf
) tail
)))))
1088 (setf (fd-stream-listen stream
) nil
)
1089 (setf (values count errno
)
1090 (os-read fd
(sap+ sap tail
) (- length tail
)))
1091 (cond ((or (and (integerp count
) (zerop count
))
1092 ;; Evidently, windows doesn't give you a
1093 ;; zero-length read for a closed pipe, but
1095 #!+win32-uses-file-handles
1097 (eql errno sb
!win32
:error_broken_pipe
)))
1098 (setf (fd-stream-listen stream
) :eof
)
1099 (/show0
"THROWing EOF-INPUT-CATCHER")
1100 (throw 'eof-input-catcher nil
))
1103 (return :read-error
)
1105 (if (eql errno sb
!unix
:ewouldblock
)
1106 (return :wait-for-input
)
1107 (return :read-error
)))
1109 ;; Success! (Do not use INCF, for sake of other threads.)
1110 (setf (buffer-tail ibuf
) (+ count tail
))))))))))
1113 ;;; Make sure there are at least BYTES number of bytes in the input
1114 ;;; buffer. Keep calling REFILL-INPUT-BUFFER until that condition is met.
1115 (defmacro input-at-least
(stream bytes
)
1116 (let ((stream-var (gensym "STREAM"))
1117 (bytes-var (gensym "BYTES"))
1118 (buffer-var (gensym "IBUF")))
1119 `(let* ((,stream-var
,stream
)
1121 (,buffer-var
(fd-stream-ibuf ,stream-var
)))
1123 (when (>= (- (buffer-tail ,buffer-var
)
1124 (buffer-head ,buffer-var
))
1127 (refill-input-buffer ,stream-var
)))))
1129 (defmacro input-wrapper
/variable-width
((stream bytes eof-error eof-value
)
1131 (let ((stream-var (gensym "STREAM"))
1132 (retry-var (gensym "RETRY"))
1133 (element-var (gensym "ELT")))
1134 `(let* ((,stream-var
,stream
)
1135 (ibuf (fd-stream-ibuf ,stream-var
))
1137 (if (fd-stream-unread ,stream-var
)
1139 (fd-stream-unread ,stream-var
)
1140 (setf (fd-stream-unread ,stream-var
) nil
)
1141 (setf (fd-stream-listen ,stream-var
) nil
))
1142 (let ((,element-var nil
)
1143 (decode-break-reason nil
))
1144 (do ((,retry-var t
))
1147 (catch 'eof-input-catcher
1148 (setf decode-break-reason
1149 (block decode-break-reason
1150 (input-at-least ,stream-var
1)
1151 (let* ((byte (sap-ref-8 (buffer-sap ibuf
)
1152 (buffer-head ibuf
))))
1153 (declare (ignorable byte
))
1155 (input-at-least ,stream-var size
)
1156 (setq ,element-var
(locally ,@read-forms
))
1157 (setq ,retry-var nil
))
1159 (when decode-break-reason
1160 (stream-decoding-error-and-handle stream
1161 decode-break-reason
))
1163 (let ((octet-count (- (buffer-tail ibuf
)
1164 (buffer-head ibuf
))))
1165 (when (or (zerop octet-count
)
1166 (and (not ,element-var
)
1167 (not decode-break-reason
)
1168 (stream-decoding-error-and-handle
1169 stream octet-count
)))
1170 (setq ,retry-var nil
)))))
1172 (incf (buffer-head ibuf
) size
)
1175 (eof-or-lose ,stream-var
,eof-error
,eof-value
))))))))
1177 ;;; a macro to wrap around all input routines to handle EOF-ERROR noise
1178 (defmacro input-wrapper
((stream bytes eof-error eof-value
) &body read-forms
)
1179 (let ((stream-var (gensym "STREAM"))
1180 (element-var (gensym "ELT")))
1181 `(let* ((,stream-var
,stream
)
1182 (ibuf (fd-stream-ibuf ,stream-var
)))
1183 (if (fd-stream-unread ,stream-var
)
1185 (fd-stream-unread ,stream-var
)
1186 (setf (fd-stream-unread ,stream-var
) nil
)
1187 (setf (fd-stream-listen ,stream-var
) nil
))
1189 (catch 'eof-input-catcher
1190 (input-at-least ,stream-var
,bytes
)
1191 (locally ,@read-forms
))))
1193 (incf (buffer-head (fd-stream-ibuf ,stream-var
)) ,bytes
)
1196 (eof-or-lose ,stream-var
,eof-error
,eof-value
))))))))
1198 (defmacro def-input-routine
/variable-width
(name
1199 (type external-format size sap head
)
1202 (defun ,name
(stream eof-error eof-value
)
1203 (input-wrapper/variable-width
(stream ,size eof-error eof-value
)
1204 (let ((,sap
(buffer-sap ibuf
))
1205 (,head
(buffer-head ibuf
)))
1207 (setf *input-routines
*
1208 (nconc *input-routines
*
1209 (list (list ',type
',name
1 ',external-format
))))))
1211 (defmacro def-input-routine
(name
1212 (type size sap head
)
1215 (defun ,name
(stream eof-error eof-value
)
1216 (input-wrapper (stream ,size eof-error eof-value
)
1217 (let ((,sap
(buffer-sap ibuf
))
1218 (,head
(buffer-head ibuf
)))
1220 (setf *input-routines
*
1221 (nconc *input-routines
*
1222 (list (list ',type
',name
',size nil
))))))
1224 ;;; STREAM-IN routine for reading a string char
1225 (def-input-routine input-character
1226 (character 1 sap head
)
1227 (code-char (sap-ref-8 sap head
)))
1229 ;;; STREAM-IN routine for reading an unsigned 8 bit number
1230 (def-input-routine input-unsigned-8bit-byte
1231 ((unsigned-byte 8) 1 sap head
)
1232 (sap-ref-8 sap head
))
1234 ;;; STREAM-IN routine for reading a signed 8 bit number
1235 (def-input-routine input-signed-8bit-number
1236 ((signed-byte 8) 1 sap head
)
1237 (signed-sap-ref-8 sap head
))
1239 ;;; STREAM-IN routine for reading an unsigned 16 bit number
1240 (def-input-routine input-unsigned-16bit-byte
1241 ((unsigned-byte 16) 2 sap head
)
1242 (sap-ref-16 sap head
))
1244 ;;; STREAM-IN routine for reading a signed 16 bit number
1245 (def-input-routine input-signed-16bit-byte
1246 ((signed-byte 16) 2 sap head
)
1247 (signed-sap-ref-16 sap head
))
1249 ;;; STREAM-IN routine for reading a unsigned 32 bit number
1250 (def-input-routine input-unsigned-32bit-byte
1251 ((unsigned-byte 32) 4 sap head
)
1252 (sap-ref-32 sap head
))
1254 ;;; STREAM-IN routine for reading a signed 32 bit number
1255 (def-input-routine input-signed-32bit-byte
1256 ((signed-byte 32) 4 sap head
)
1257 (signed-sap-ref-32 sap head
))
1259 #+#.
(cl:if
(cl:= sb
!vm
:n-word-bits
64) '(and) '(or))
1261 (def-input-routine input-unsigned-64bit-byte
1262 ((unsigned-byte 64) 8 sap head
)
1263 (sap-ref-64 sap head
))
1264 (def-input-routine input-signed-64bit-byte
1265 ((signed-byte 64) 8 sap head
)
1266 (signed-sap-ref-64 sap head
)))
1268 ;;; Find an input routine to use given the type. Return as multiple
1269 ;;; values the routine, the real type transfered, and the number of
1270 ;;; bytes per element (and for character types string input routine).
1271 (defun pick-input-routine (type &optional external-format
)
1272 (when (subtypep type
'character
)
1273 (dolist (entry *external-formats
*)
1274 (when (member external-format
(first entry
))
1275 (return-from pick-input-routine
1276 (values (symbol-function (third entry
))
1279 (symbol-function (second entry
))
1280 (first (first entry
)))))))
1281 (dolist (entry *input-routines
*)
1282 (when (and (subtypep type
(first entry
))
1283 (or (not (fourth entry
))
1284 (eq external-format
(fourth entry
))))
1285 (return-from pick-input-routine
1286 (values (symbol-function (second entry
))
1289 ;; FIXME: let's do it the hard way, then (but ignore things like
1290 ;; endianness, efficiency, and the necessary coupling between these
1291 ;; and the output routines). -- CSR, 2004-02-09
1292 (loop for i from
40 by
8 to
1024 ; ARB (well, KLUDGE really)
1293 if
(subtypep type
`(unsigned-byte ,i
))
1294 do
(return-from pick-input-routine
1296 (lambda (stream eof-error eof-value
)
1297 (input-wrapper (stream (/ i
8) eof-error eof-value
)
1298 (let ((sap (buffer-sap ibuf
))
1299 (head (buffer-head ibuf
)))
1300 (loop for j from
0 below
(/ i
8)
1304 (sap-ref-8 sap
(+ head j
))))
1305 finally
(return result
)))))
1308 (loop for i from
40 by
8 to
1024 ; ARB (well, KLUDGE really)
1309 if
(subtypep type
`(signed-byte ,i
))
1310 do
(return-from pick-input-routine
1312 (lambda (stream eof-error eof-value
)
1313 (input-wrapper (stream (/ i
8) eof-error eof-value
)
1314 (let ((sap (buffer-sap ibuf
))
1315 (head (buffer-head ibuf
)))
1316 (loop for j from
0 below
(/ i
8)
1320 (sap-ref-8 sap
(+ head j
))))
1321 finally
(return (if (logbitp (1- i
) result
)
1322 (dpb result
(byte i
0) -
1)
1327 ;;; the N-BIN method for FD-STREAMs
1329 ;;; Note that this blocks in UNIX-READ. It is generally used where
1330 ;;; there is a definite amount of reading to be done, so blocking
1331 ;;; isn't too problematical.
1332 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p
1333 &aux
(total-copied 0))
1334 (declare (type fd-stream stream
))
1335 (declare (type index start requested total-copied
))
1336 (let ((unread (fd-stream-unread stream
)))
1338 ;; AVERs designed to fail when we have more complicated
1339 ;; character representations.
1340 (aver (typep unread
'base-char
))
1341 (aver (= (fd-stream-element-size stream
) 1))
1342 ;; KLUDGE: this is a slightly-unrolled-and-inlined version of
1345 (system-area-pointer
1346 (setf (sap-ref-8 buffer start
) (char-code unread
)))
1347 ((simple-unboxed-array (*))
1348 (setf (aref buffer start
) unread
)))
1349 (setf (fd-stream-unread stream
) nil
)
1350 (setf (fd-stream-listen stream
) nil
)
1351 (incf total-copied
)))
1354 (let* ((remaining-request (- requested total-copied
))
1355 (ibuf (fd-stream-ibuf stream
))
1356 (head (buffer-head ibuf
))
1357 (tail (buffer-tail ibuf
))
1358 (available (- tail head
))
1359 (n-this-copy (min remaining-request available
))
1360 (this-start (+ start total-copied
))
1361 (this-end (+ this-start n-this-copy
))
1362 (sap (buffer-sap ibuf
)))
1363 (declare (type index remaining-request head tail available
))
1364 (declare (type index n-this-copy
))
1365 ;; Copy data from stream buffer into user's buffer.
1366 (%byte-blt sap head buffer this-start this-end
)
1367 (incf (buffer-head ibuf
) n-this-copy
)
1368 (incf total-copied n-this-copy
)
1369 ;; Maybe we need to refill the stream buffer.
1370 (cond (;; If there were enough data in the stream buffer, we're done.
1371 (eql total-copied requested
)
1372 (return total-copied
))
1373 (;; If EOF, we're done in another way.
1374 (null (catch 'eof-input-catcher
(refill-input-buffer stream
)))
1376 (error 'end-of-file
:stream stream
)
1377 (return total-copied
)))
1378 ;; Otherwise we refilled the stream buffer, so fall
1379 ;; through into another pass of the loop.
1382 (defun fd-stream-resync (stream)
1383 (dolist (entry *external-formats
*)
1384 (when (member (fd-stream-external-format stream
) (first entry
))
1385 (return-from fd-stream-resync
1386 (funcall (symbol-function (eighth entry
)) stream
)))))
1388 (defun get-fd-stream-character-sizer (stream)
1389 (dolist (entry *external-formats
*)
1390 (when (member (fd-stream-external-format stream
) (first entry
))
1391 (return-from get-fd-stream-character-sizer
(ninth entry
)))))
1393 (defun fd-stream-character-size (stream char
)
1394 (let ((sizer (get-fd-stream-character-sizer stream
)))
1395 (when sizer
(funcall sizer char
))))
1397 (defun fd-stream-string-size (stream string
)
1398 (let ((sizer (get-fd-stream-character-sizer stream
)))
1400 (loop for char across string summing
(funcall sizer char
)))))
1402 (defun find-external-format (external-format)
1403 (when external-format
1404 (find external-format
*external-formats
* :test
#'member
:key
#'car
)))
1406 (defun variable-width-external-format-p (ef-entry)
1407 (when (eighth ef-entry
) t
))
1409 (defun bytes-for-char-fun (ef-entry)
1410 (if ef-entry
(symbol-function (ninth ef-entry
)) (constantly 1)))
1412 ;;; FIXME: OAOOM here vrt. *EXTERNAL-FORMAT-FUNCTIONS* in fd-stream.lisp
1413 (defmacro define-external-format
(external-format size output-restart
1415 (let* ((name (first external-format
))
1416 (out-function (symbolicate "OUTPUT-BYTES/" name
))
1417 (format (format nil
"OUTPUT-CHAR-~A-~~A-BUFFERED" (string name
)))
1418 (in-function (symbolicate "FD-STREAM-READ-N-CHARACTERS/" name
))
1419 (in-char-function (symbolicate "INPUT-CHAR/" name
))
1420 (size-function (symbolicate "BYTES-FOR-CHAR/" name
))
1421 (read-c-string-function (symbolicate "READ-FROM-C-STRING/" name
))
1422 (output-c-string-function (symbolicate "OUTPUT-TO-C-STRING/" name
))
1423 (n-buffer (gensym "BUFFER")))
1425 (defun ,size-function
(byte)
1426 (declare (ignore byte
))
1428 (defun ,out-function
(stream string flush-p start end
)
1429 (let ((start (or start
0))
1430 (end (or end
(length string
))))
1431 (declare (type index start end
))
1432 (synchronize-stream-output stream
)
1433 (unless (<= 0 start end
(length string
))
1434 (sequence-bounding-indices-bad-error string start end
))
1437 (let ((obuf (fd-stream-obuf stream
)))
1438 (setf (buffer-tail obuf
)
1439 (string-dispatch (simple-base-string
1441 (simple-array character
(*))
1444 (let ((sap (buffer-sap obuf
))
1445 (len (buffer-length obuf
))
1447 (tail (buffer-tail obuf
)))
1448 (declare (type index tail
)
1449 ;; STRING bounds have already been checked.
1450 (optimize (safety 0)))
1452 (,@(if output-restart
1453 `(catch 'output-nothing
)
1456 ((or (= start end
) (< (- len tail
) 4)))
1457 (let* ((byte (aref string start
))
1458 (bits (char-code byte
)))
1462 ;; Exited from the loop normally
1464 ;; Exited via CATCH. Skip the current character
1465 ;; and try the inner loop again.
1468 (flush-output-buffer stream
)))
1470 (flush-output-buffer stream
))))
1471 (def-output-routines (,format
1477 (if (eql byte
#\Newline
)
1478 (setf (fd-stream-char-pos stream
) 0)
1479 (incf (fd-stream-char-pos stream
)))
1480 (let* ((obuf (fd-stream-obuf stream
))
1481 (bits (char-code byte
))
1482 (sap (buffer-sap obuf
))
1483 (tail (buffer-tail obuf
)))
1485 (defun ,in-function
(stream buffer start requested eof-error-p
1486 &aux
(index start
) (end (+ start requested
)))
1487 (declare (type fd-stream stream
)
1488 (type index start requested index end
)
1490 (simple-array character
(#.
+ansi-stream-in-buffer-length
+))
1492 (let ((unread (fd-stream-unread stream
)))
1494 (setf (aref buffer index
) unread
)
1495 (setf (fd-stream-unread stream
) nil
)
1496 (setf (fd-stream-listen stream
) nil
)
1500 (let* ((ibuf (fd-stream-ibuf stream
))
1501 (head (buffer-head ibuf
))
1502 (tail (buffer-tail ibuf
))
1503 (sap (buffer-sap ibuf
)))
1504 (declare (type index head tail
)
1505 (type system-area-pointer sap
))
1506 ;; Copy data from stream buffer into user's buffer.
1507 (dotimes (i (min (truncate (- tail head
) ,size
)
1509 (declare (optimize speed
))
1510 (let* ((byte (sap-ref-8 sap head
)))
1511 (setf (aref buffer index
) ,in-expr
)
1514 (setf (buffer-head ibuf
) head
)
1515 ;; Maybe we need to refill the stream buffer.
1516 (cond ( ;; If there was enough data in the stream buffer, we're done.
1518 (return (- index start
)))
1519 ( ;; If EOF, we're done in another way.
1520 (null (catch 'eof-input-catcher
(refill-input-buffer stream
)))
1522 (error 'end-of-file
:stream stream
)
1523 (return (- index start
))))
1524 ;; Otherwise we refilled the stream buffer, so fall
1525 ;; through into another pass of the loop.
1527 (def-input-routine ,in-char-function
(character ,size sap head
)
1528 (let ((byte (sap-ref-8 sap head
)))
1530 (defun ,read-c-string-function
(sap element-type
)
1531 (declare (type system-area-pointer sap
)
1532 (type (member character base-char
) element-type
))
1534 (declare (optimize (speed 3) (safety 0)))
1535 (let* ((stream ,name
)
1537 (loop for head of-type index upfrom
0 by
,size
1538 for count of-type index upto
(1- array-dimension-limit
)
1539 for byte
= (sap-ref-8 sap head
)
1540 for char of-type character
= ,in-expr
1541 until
(zerop (char-code char
))
1542 finally
(return count
)))
1543 ;; Inline the common cases
1544 (string (make-string length
:element-type element-type
)))
1545 (declare (ignorable stream
)
1547 (type simple-string string
))
1548 (/show0 before-copy-loop
)
1549 (loop for head of-type index upfrom
0 by
,size
1550 for index of-type index below length
1551 for byte
= (sap-ref-8 sap head
)
1552 for char of-type character
= ,in-expr
1553 do
(setf (aref string index
) char
))
1554 string
))) ;; last loop rewrite to dotimes?
1555 (defun ,output-c-string-function
(string)
1556 (declare (type simple-string string
))
1558 (declare (optimize (speed 3) (safety 0)))
1559 (let* ((length (length string
))
1560 (,n-buffer
(make-array (* (1+ length
) ,size
)
1561 :element-type
'(unsigned-byte 8)))
1564 (declare (type index length tail
))
1565 (with-pinned-objects (,n-buffer
)
1566 (let ((sap (vector-sap ,n-buffer
)))
1567 (declare (system-area-pointer sap
))
1569 (let* ((byte (aref string i
))
1570 (bits (char-code byte
)))
1571 (declare (ignorable byte bits
))
1575 (byte (code-char bits
)))
1576 (declare (ignorable bits byte
))
1579 (setf *external-formats
*
1580 (cons '(,external-format
,in-function
,in-char-function
,out-function
1581 ,@(mapcar #'(lambda (buffering)
1582 (intern (format nil format
(string buffering
))))
1583 '(:none
:line
:full
))
1584 nil
; no resync-function
1585 ,size-function
,read-c-string-function
,output-c-string-function
)
1586 *external-formats
*)))))
1588 (defmacro define-external-format
/variable-width
1589 (external-format output-restart out-size-expr
1590 out-expr in-size-expr in-expr
)
1591 (let* ((name (first external-format
))
1592 (out-function (symbolicate "OUTPUT-BYTES/" name
))
1593 (format (format nil
"OUTPUT-CHAR-~A-~~A-BUFFERED" (string name
)))
1594 (in-function (symbolicate "FD-STREAM-READ-N-CHARACTERS/" name
))
1595 (in-char-function (symbolicate "INPUT-CHAR/" name
))
1596 (resync-function (symbolicate "RESYNC/" name
))
1597 (size-function (symbolicate "BYTES-FOR-CHAR/" name
))
1598 (read-c-string-function (symbolicate "READ-FROM-C-STRING/" name
))
1599 (output-c-string-function (symbolicate "OUTPUT-TO-C-STRING/" name
))
1600 (n-buffer (gensym "BUFFER")))
1602 (defun ,size-function
(byte)
1603 (declare (ignorable byte
))
1605 (defun ,out-function
(stream string flush-p start end
)
1606 (let ((start (or start
0))
1607 (end (or end
(length string
))))
1608 (declare (type index start end
))
1609 (synchronize-stream-output stream
)
1610 (unless (<= 0 start end
(length string
))
1611 (sequence-bounding-indices-bad string start end
))
1614 (let ((obuf (fd-stream-obuf stream
)))
1615 (setf (buffer-tail obuf
)
1616 (string-dispatch (simple-base-string
1618 (simple-array character
(*))
1621 (let ((len (buffer-length obuf
))
1622 (sap (buffer-sap obuf
))
1624 (tail (buffer-tail obuf
)))
1625 (declare (type index tail
)
1626 ;; STRING bounds have already been checked.
1627 (optimize (safety 0)))
1629 (,@(if output-restart
1630 `(catch 'output-nothing
)
1633 ((or (= start end
) (< (- len tail
) 4)))
1634 (let* ((byte (aref string start
))
1635 (bits (char-code byte
))
1636 (size ,out-size-expr
))
1640 ;; Exited from the loop normally
1642 ;; Exited via CATCH. Skip the current character
1643 ;; and try the inner loop again.
1646 (flush-output-buffer stream
)))
1648 (flush-output-buffer stream
))))
1649 (def-output-routines/variable-width
(,format
1656 (if (eql byte
#\Newline
)
1657 (setf (fd-stream-char-pos stream
) 0)
1658 (incf (fd-stream-char-pos stream
)))
1659 (let ((bits (char-code byte
))
1660 (sap (buffer-sap obuf
))
1661 (tail (buffer-tail obuf
)))
1663 (defun ,in-function
(stream buffer start requested eof-error-p
1664 &aux
(total-copied 0))
1665 (declare (type fd-stream stream
)
1666 (type index start requested total-copied
)
1668 (simple-array character
(#.
+ansi-stream-in-buffer-length
+))
1670 (let ((unread (fd-stream-unread stream
)))
1672 (setf (aref buffer start
) unread
)
1673 (setf (fd-stream-unread stream
) nil
)
1674 (setf (fd-stream-listen stream
) nil
)
1675 (incf total-copied
)))
1678 (let* ((ibuf (fd-stream-ibuf stream
))
1679 (head (buffer-head ibuf
))
1680 (tail (buffer-tail ibuf
))
1681 (sap (buffer-sap ibuf
))
1682 (decode-break-reason nil
))
1683 (declare (type index head tail
))
1684 ;; Copy data from stream buffer into user's buffer.
1685 (do ((size nil nil
))
1686 ((or (= tail head
) (= requested total-copied
)))
1687 (setf decode-break-reason
1688 (block decode-break-reason
1689 (let ((byte (sap-ref-8 sap head
)))
1690 (declare (ignorable byte
))
1691 (setq size
,in-size-expr
)
1692 (when (> size
(- tail head
))
1694 (setf (aref buffer
(+ start total-copied
)) ,in-expr
)
1698 (setf (buffer-head ibuf
) head
)
1699 (when decode-break-reason
1700 ;; If we've already read some characters on when the invalid
1701 ;; code sequence is detected, we return immediately. The
1702 ;; handling of the error is deferred until the next call
1703 ;; (where this check will be false). This allows establishing
1704 ;; high-level handlers for decode errors (for example
1705 ;; automatically resyncing in Lisp comments).
1706 (when (plusp total-copied
)
1707 (return-from ,in-function total-copied
))
1708 (when (stream-decoding-error-and-handle
1709 stream decode-break-reason
)
1711 (error 'end-of-file
:stream stream
)
1712 (return-from ,in-function total-copied
)))
1713 (setf head
(buffer-head ibuf
))
1714 (setf tail
(buffer-tail ibuf
))))
1715 (setf (buffer-head ibuf
) head
)
1716 ;; Maybe we need to refill the stream buffer.
1717 (cond ( ;; If there were enough data in the stream buffer, we're done.
1718 (= total-copied requested
)
1719 (return total-copied
))
1720 ( ;; If EOF, we're done in another way.
1721 (or (eq decode-break-reason
'eof
)
1722 (null (catch 'eof-input-catcher
1723 (refill-input-buffer stream
))))
1725 (error 'end-of-file
:stream stream
)
1726 (return total-copied
)))
1727 ;; Otherwise we refilled the stream buffer, so fall
1728 ;; through into another pass of the loop.
1730 (def-input-routine/variable-width
,in-char-function
(character
1734 (let ((byte (sap-ref-8 sap head
)))
1735 (declare (ignorable byte
))
1737 (defun ,resync-function
(stream)
1738 (let ((ibuf (fd-stream-ibuf stream
)))
1740 (input-at-least stream
2)
1741 (incf (buffer-head ibuf
))
1742 (unless (block decode-break-reason
1743 (let* ((sap (buffer-sap ibuf
))
1744 (head (buffer-head ibuf
))
1745 (byte (sap-ref-8 sap head
))
1746 (size ,in-size-expr
))
1747 (declare (ignorable byte
))
1748 (input-at-least stream size
)
1749 (setf head
(buffer-head ibuf
))
1753 (defun ,read-c-string-function
(sap element-type
)
1754 (declare (type system-area-pointer sap
))
1756 (declare (optimize (speed 3) (safety 0)))
1757 (let* ((stream ,name
)
1758 (size 0) (head 0) (byte 0) (char nil
)
1759 (decode-break-reason nil
)
1760 (length (dotimes (count (1- ARRAY-DIMENSION-LIMIT
) count
)
1761 (setf decode-break-reason
1762 (block decode-break-reason
1763 (setf byte
(sap-ref-8 sap head
)
1768 (when decode-break-reason
1769 (c-string-decoding-error ,name decode-break-reason
))
1770 (when (zerop (char-code char
))
1772 (string (make-string length
:element-type element-type
)))
1773 (declare (ignorable stream
)
1774 (type index head length
) ;; size
1775 (type (unsigned-byte 8) byte
)
1776 (type (or null character
) char
)
1777 (type string string
))
1779 (dotimes (index length string
)
1780 (setf decode-break-reason
1781 (block decode-break-reason
1782 (setf byte
(sap-ref-8 sap head
)
1787 (when decode-break-reason
1788 (c-string-decoding-error ,name decode-break-reason
))
1789 (setf (aref string index
) char
)))))
1791 (defun ,output-c-string-function
(string)
1792 (declare (type simple-string string
))
1794 (declare (optimize (speed 3) (safety 0)))
1795 (let* ((length (length string
))
1796 (char-length (make-array (1+ length
) :element-type
'index
))
1798 (+ (loop for i of-type index below length
1799 for byte of-type character
= (aref string i
)
1800 for bits
= (char-code byte
)
1801 sum
(setf (aref char-length i
)
1802 (the index
,out-size-expr
)))
1803 (let* ((byte (code-char 0))
1804 (bits (char-code byte
)))
1805 (declare (ignorable byte bits
))
1806 (setf (aref char-length length
)
1807 (the index
,out-size-expr
)))))
1809 (,n-buffer
(make-array buffer-length
1810 :element-type
'(unsigned-byte 8)))
1812 (declare (type index length buffer-length tail
)
1815 (with-pinned-objects (,n-buffer
)
1816 (let ((sap (vector-sap ,n-buffer
)))
1817 (declare (system-area-pointer sap
))
1818 (loop for i of-type index below length
1819 for byte of-type character
= (aref string i
)
1820 for bits
= (char-code byte
)
1821 for size of-type index
= (aref char-length i
)
1826 (byte (code-char bits
))
1827 (size (aref char-length length
)))
1828 (declare (ignorable bits byte size
))
1832 (setf *external-formats
*
1833 (cons '(,external-format
,in-function
,in-char-function
,out-function
1834 ,@(mapcar #'(lambda (buffering)
1835 (intern (format nil format
(string buffering
))))
1836 '(:none
:line
:full
))
1838 ,size-function
,read-c-string-function
,output-c-string-function
)
1839 *external-formats
*)))))
1841 ;;; Multiple names for the :ISO{,-}8859-* families are needed because on
1842 ;;; FreeBSD (and maybe other BSD systems), nl_langinfo("LATIN-1") will
1843 ;;; return "ISO8859-1" instead of "ISO-8859-1".
1844 (define-external-format (:latin-1
:latin1
:iso-8859-1
:iso8859-1
)
1847 (external-format-encoding-error stream bits
)
1848 (setf (sap-ref-8 sap tail
) bits
))
1851 (define-external-format (:ascii
:us-ascii
:ansi_x3.4-
1968
1852 :iso-646
:iso-646-us
:|
646|
)
1855 (external-format-encoding-error stream bits
)
1856 (setf (sap-ref-8 sap tail
) bits
))
1859 (let* ((table (let ((s (make-string 256)))
1860 (map-into s
#'code-char
1861 '(#x00
#x01
#x02
#x03
#x9c
#x09
#x86
#x7f
#x97
#x8d
#x8e
#x0b
#x0c
#x0d
#x0e
#x0f
1862 #x10
#x11
#x12
#x13
#x9d
#x85
#x08
#x87
#x18
#x19
#x92
#x8f
#x1c
#x1d
#x1e
#x1f
1863 #x80
#x81
#x82
#x83
#x84
#x0a
#x17
#x1b
#x88
#x89
#x8a
#x8b
#x8c
#x05
#x06
#x07
1864 #x90
#x91
#x16
#x93
#x94
#x95
#x96
#x04
#x98
#x99
#x9a
#x9b
#x14
#x15
#x9e
#x1a
1865 #x20
#xa0
#xe2
#xe4
#xe0
#xe1
#xe3
#xe5
#xe7
#xf1
#xa2
#x2e
#x3c
#x28
#x2b
#x7c
1866 #x26
#xe9
#xea
#xeb
#xe8
#xed
#xee
#xef
#xec
#xdf
#x21
#x24
#x2a
#x29
#x3b
#xac
1867 #x2d
#x2f
#xc2
#xc4
#xc0
#xc1
#xc3
#xc5
#xc7
#xd1
#xa6
#x2c
#x25
#x5f
#x3e
#x3f
1868 #xf8
#xc9
#xca
#xcb
#xc8
#xcd
#xce
#xcf
#xcc
#x60
#x3a
#x23
#x40
#x27
#x3d
#x22
1869 #xd8
#x61
#x62
#x63
#x64
#x65
#x66
#x67
#x68
#x69
#xab
#xbb
#xf0
#xfd
#xfe
#xb1
1870 #xb0
#x6a
#x6b
#x6c
#x6d
#x6e
#x6f
#x70
#x71
#x72
#xaa
#xba
#xe6
#xb8
#xc6
#xa4
1871 #xb5
#x7e
#x73
#x74
#x75
#x76
#x77
#x78
#x79
#x7a
#xa1
#xbf
#xd0
#xdd
#xde
#xae
1872 #x5e
#xa3
#xa5
#xb7
#xa9
#xa7
#xb6
#xbc
#xbd
#xbe
#x5b
#x5d
#xaf
#xa8
#xb4
#xd7
1873 #x7b
#x41
#x42
#x43
#x44
#x45
#x46
#x47
#x48
#x49
#xad
#xf4
#xf6
#xf2
#xf3
#xf5
1874 #x7d
#x4a
#x4b
#x4c
#x4d
#x4e
#x4f
#x50
#x51
#x52
#xb9
#xfb
#xfc
#xf9
#xfa
#xff
1875 #x5c
#xf7
#x53
#x54
#x55
#x56
#x57
#x58
#x59
#x5a
#xb2
#xd4
#xd6
#xd2
#xd3
#xd5
1876 #x30
#x31
#x32
#x33
#x34
#x35
#x36
#x37
#x38
#x39
#xb3
#xdb
#xdc
#xd9
#xda
#x9f
))
1878 (reverse-table (let ((rt (make-array 256 :element-type
'(unsigned-byte 8) :initial-element
0)))
1879 (loop for char across table for i from
0
1880 do
(aver (= 0 (aref rt
(char-code char
))))
1881 do
(setf (aref rt
(char-code char
)) i
))
1883 (define-external-format (:ebcdic-us
:ibm-037
:ibm037
)
1886 (external-format-encoding-error stream bits
)
1887 (setf (sap-ref-8 sap tail
) (aref reverse-table bits
)))
1892 (let ((latin-9-table (let ((table (make-string 256)))
1895 (setf (aref table i
) (code-char i
)))
1896 (setf (aref table
#xa4
) (code-char #x20ac
))
1897 (setf (aref table
#xa6
) (code-char #x0160
))
1898 (setf (aref table
#xa8
) (code-char #x0161
))
1899 (setf (aref table
#xb4
) (code-char #x017d
))
1900 (setf (aref table
#xb8
) (code-char #x017e
))
1901 (setf (aref table
#xbc
) (code-char #x0152
))
1902 (setf (aref table
#xbd
) (code-char #x0153
))
1903 (setf (aref table
#xbe
) (code-char #x0178
))
1905 (latin-9-reverse-1 (make-array 16
1906 :element-type
'(unsigned-byte 21)
1907 :initial-contents
'(#x0160
#x0161
#x0152
#x0153
0 0 0 0 #x0178
0 0 0 #x20ac
#x017d
#x017e
0)))
1908 (latin-9-reverse-2 (make-array 16
1909 :element-type
'(unsigned-byte 8)
1910 :initial-contents
'(#xa6
#xa8
#xbc
#xbd
0 0 0 0 #xbe
0 0 0 #xa4
#xb4
#xb8
0))))
1911 (define-external-format (:latin-9
:latin9
:iso-8859-15
:iso8859-15
)
1913 (setf (sap-ref-8 sap tail
)
1915 (if (= bits
(char-code (aref latin-9-table bits
)))
1917 (external-format-encoding-error stream byte
))
1918 (if (= (aref latin-9-reverse-1
(logand bits
15)) bits
)
1919 (aref latin-9-reverse-2
(logand bits
15))
1920 (external-format-encoding-error stream byte
))))
1921 (aref latin-9-table byte
)))
1923 (define-external-format/variable-width
(:utf-8
:utf8
) nil
1924 (let ((bits (char-code byte
)))
1925 (cond ((< bits
#x80
) 1)
1927 ((< bits
#x10000
) 3)
1930 (1 (setf (sap-ref-8 sap tail
) bits
))
1931 (2 (setf (sap-ref-8 sap tail
) (logior #xc0
(ldb (byte 5 6) bits
))
1932 (sap-ref-8 sap
(+ 1 tail
)) (logior #x80
(ldb (byte 6 0) bits
))))
1933 (3 (setf (sap-ref-8 sap tail
) (logior #xe0
(ldb (byte 4 12) bits
))
1934 (sap-ref-8 sap
(+ 1 tail
)) (logior #x80
(ldb (byte 6 6) bits
))
1935 (sap-ref-8 sap
(+ 2 tail
)) (logior #x80
(ldb (byte 6 0) bits
))))
1936 (4 (setf (sap-ref-8 sap tail
) (logior #xf0
(ldb (byte 3 18) bits
))
1937 (sap-ref-8 sap
(+ 1 tail
)) (logior #x80
(ldb (byte 6 12) bits
))
1938 (sap-ref-8 sap
(+ 2 tail
)) (logior #x80
(ldb (byte 6 6) bits
))
1939 (sap-ref-8 sap
(+ 3 tail
)) (logior #x80
(ldb (byte 6 0) bits
)))))
1940 (cond ((< byte
#x80
) 1)
1941 ((< byte
#xc2
) (return-from decode-break-reason
1))
1945 (code-char (ecase size
1947 (2 (let ((byte2 (sap-ref-8 sap
(1+ head
))))
1948 (unless (<= #x80 byte2
#xbf
)
1949 (return-from decode-break-reason
2))
1950 (dpb byte
(byte 5 6) byte2
)))
1951 (3 (let ((byte2 (sap-ref-8 sap
(1+ head
)))
1952 (byte3 (sap-ref-8 sap
(+ 2 head
))))
1953 (unless (and (<= #x80 byte2
#xbf
)
1954 (<= #x80 byte3
#xbf
))
1955 (return-from decode-break-reason
3))
1956 (dpb byte
(byte 4 12) (dpb byte2
(byte 6 6) byte3
))))
1957 (4 (let ((byte2 (sap-ref-8 sap
(1+ head
)))
1958 (byte3 (sap-ref-8 sap
(+ 2 head
)))
1959 (byte4 (sap-ref-8 sap
(+ 3 head
))))
1960 (unless (and (<= #x80 byte2
#xbf
)
1961 (<= #x80 byte3
#xbf
)
1962 (<= #x80 byte4
#xbf
))
1963 (return-from decode-break-reason
4))
1964 (dpb byte
(byte 3 18)
1965 (dpb byte2
(byte 6 12)
1966 (dpb byte3
(byte 6 6) byte4
))))))))
1968 ;;;; utility functions (misc routines, etc)
1970 ;;; Fill in the various routine slots for the given type. INPUT-P and
1971 ;;; OUTPUT-P indicate what slots to fill. The buffering slot must be
1972 ;;; set prior to calling this routine.
1973 (defun set-fd-stream-routines (fd-stream element-type external-format
1974 input-p output-p buffer-p
)
1975 (let* ((target-type (case element-type
1976 (unsigned-byte '(unsigned-byte 8))
1977 (signed-byte '(signed-byte 8))
1978 (:default
'character
)
1980 (character-stream-p (subtypep target-type
'character
))
1981 (bivalent-stream-p (eq element-type
:default
))
1982 normalized-external-format
1983 (bin-routine #'ill-bin
)
1986 (cin-routine #'ill-in
)
1989 (input-type nil
) ;calculated from bin-type/cin-type
1990 (input-size nil
) ;calculated from bin-size/cin-size
1991 (read-n-characters #'ill-in
)
1992 (bout-routine #'ill-bout
)
1995 (cout-routine #'ill-out
)
2000 (output-bytes #'ill-bout
))
2002 ;; Ensure that we have buffers in the desired direction(s) only,
2003 ;; getting new ones and dropping/resetting old ones as necessary.
2004 (let ((obuf (fd-stream-obuf fd-stream
)))
2008 (setf (fd-stream-obuf fd-stream
) (get-buffer)))
2010 (setf (fd-stream-obuf fd-stream
) nil
)
2011 (release-buffer obuf
))))
2013 (let ((ibuf (fd-stream-ibuf fd-stream
)))
2017 (setf (fd-stream-ibuf fd-stream
) (get-buffer)))
2019 (setf (fd-stream-ibuf fd-stream
) nil
)
2020 (release-buffer ibuf
))))
2022 ;; FIXME: Why only for output? Why unconditionally?
2024 (setf (fd-stream-char-pos fd-stream
) 0))
2026 (when (and character-stream-p
2027 (eq external-format
:default
))
2028 (/show0
"/getting default external format")
2029 (setf external-format
(default-external-format)))
2032 (when (or (not character-stream-p
) bivalent-stream-p
)
2033 (multiple-value-setq (bin-routine bin-type bin-size read-n-characters
2034 normalized-external-format
)
2035 (pick-input-routine (if bivalent-stream-p
'(unsigned-byte 8)
2039 (error "could not find any input routine for ~S" target-type
)))
2040 (when character-stream-p
2041 (multiple-value-setq (cin-routine cin-type cin-size read-n-characters
2042 normalized-external-format
)
2043 (pick-input-routine target-type external-format
))
2045 (error "could not find any input routine for ~S" target-type
)))
2046 (setf (fd-stream-in fd-stream
) cin-routine
2047 (fd-stream-bin fd-stream
) bin-routine
)
2048 ;; character type gets preferential treatment
2049 (setf input-size
(or cin-size bin-size
))
2050 (setf input-type
(or cin-type bin-type
))
2051 (when normalized-external-format
2052 (setf (fd-stream-external-format fd-stream
)
2053 normalized-external-format
))
2054 (when (= (or cin-size
1) (or bin-size
1) 1)
2055 (setf (fd-stream-n-bin fd-stream
) ;XXX
2056 (if (and character-stream-p
(not bivalent-stream-p
))
2058 #'fd-stream-read-n-bytes
))
2059 ;; Sometimes turn on fast-read-char/fast-read-byte. Switch on
2060 ;; for character and (unsigned-byte 8) streams. In these
2061 ;; cases, fast-read-* will read from the
2062 ;; ansi-stream-(c)in-buffer, saving function calls.
2063 ;; Otherwise, the various data-reading functions in the stream
2064 ;; structure will be called.
2066 (not bivalent-stream-p
)
2067 ;; temporary disable on :io streams
2069 (cond (character-stream-p
2070 (setf (ansi-stream-cin-buffer fd-stream
)
2071 (make-array +ansi-stream-in-buffer-length
+
2072 :element-type
'character
)))
2073 ((equal target-type
'(unsigned-byte 8))
2074 (setf (ansi-stream-in-buffer fd-stream
)
2075 (make-array +ansi-stream-in-buffer-length
+
2076 :element-type
'(unsigned-byte 8))))))))
2079 (when (or (not character-stream-p
) bivalent-stream-p
)
2080 (multiple-value-setq (bout-routine bout-type bout-size output-bytes
2081 normalized-external-format
)
2082 (pick-output-routine (if bivalent-stream-p
2085 (fd-stream-buffering fd-stream
)
2087 (unless bout-routine
2088 (error "could not find any output routine for ~S buffered ~S"
2089 (fd-stream-buffering fd-stream
)
2091 (when character-stream-p
2092 (multiple-value-setq (cout-routine cout-type cout-size output-bytes
2093 normalized-external-format
)
2094 (pick-output-routine target-type
2095 (fd-stream-buffering fd-stream
)
2097 (unless cout-routine
2098 (error "could not find any output routine for ~S buffered ~S"
2099 (fd-stream-buffering fd-stream
)
2101 (when normalized-external-format
2102 (setf (fd-stream-external-format fd-stream
)
2103 normalized-external-format
))
2104 (when character-stream-p
2105 (setf (fd-stream-output-bytes fd-stream
) output-bytes
))
2106 (setf (fd-stream-out fd-stream
) cout-routine
2107 (fd-stream-bout fd-stream
) bout-routine
2108 (fd-stream-sout fd-stream
) (if (eql cout-size
1)
2109 #'fd-sout
#'ill-out
))
2110 (setf output-size
(or cout-size bout-size
))
2111 (setf output-type
(or cout-type bout-type
)))
2113 (when (and input-size output-size
2114 (not (eq input-size output-size
)))
2115 (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
2116 input-type input-size
2117 output-type output-size
))
2118 (setf (fd-stream-element-size fd-stream
)
2119 (or input-size output-size
))
2121 (setf (fd-stream-element-type fd-stream
)
2122 (cond ((equal input-type output-type
)
2128 ((subtypep input-type output-type
)
2130 ((subtypep output-type input-type
)
2133 (error "Input type (~S) and output type (~S) are unrelated?"
2137 ;; Unix's close(2) can fail in various ways. FIXME: look around for
2138 ;; other calls to UNIX-CLOSE, and maybe replace them with this.
2139 (defun close-descriptor (descriptor &optional signaler
)
2140 "Try to close(2) DESCRIPTOR. Retry in case close(2) fails and
2141 sets errno to EINTR. If close(2) fails and sets errno to any
2142 value other than EINTR, then use SIGNALER as follows: if SIGNALER
2143 is a function, call it with the descriptor and errno; if SIGNALER
2144 is T, signal an error of type ERROR; if SIGNALER is NIL, silently
2145 ignore the close(2) error. (In this case, we can silently leak a
2146 descriptor; don't use this unless you have to.)"
2147 (loop (multiple-value-bind (status errno
)
2148 (os-close descriptor
)
2151 (when (/= errno sb
!unix
:eintr
)
2152 (cond ((functionp signaler
)
2153 (funcall signaler descriptor errno
))
2155 (error "failed to close() fd ~D: (~A)"
2156 descriptor
(strerror errno
)))))))))
2158 ;;; Handles the resource-release aspects of stream closing, and marks
2160 (defun release-fd-stream-resources (fd-stream)
2162 ;; Disable interrupts so that a asynch unwind will not leave us
2163 ;; with a dangling finalizer (that would close the same
2164 ;; --possibly reassigned-- FD again), or a stream with a closed
2165 ;; FD that appears open.
2167 ;; Drop handlers first.
2168 (when (fd-stream-handler fd-stream
)
2169 (remove-fd-handler (fd-stream-handler fd-stream
))
2170 (setf (fd-stream-handler fd-stream
) nil
))
2171 (close-descriptor (fd-stream-fd fd-stream
)
2173 (declare (ignore fd
))
2174 (simple-stream-perror
2175 "failed to close() the descriptor in ~A"
2177 (set-closed-flame fd-stream
)
2178 (when (fboundp 'cancel-finalization
)
2179 (cancel-finalization fd-stream
)))
2180 ;; On error unwind from WITHOUT-INTERRUPTS.
2181 (serious-condition (e)
2183 ;; Release all buffers. If this is undone, or interrupted,
2184 ;; we're still safe: buffers have finalizers of their own.
2185 (release-fd-stream-buffers fd-stream
))
2187 ;;; Flushes the current input buffer and unread chatacter, and returns
2188 ;;; the input buffer, and the amount of of flushed input in bytes.
2189 (defun flush-input-buffer (stream)
2190 (let ((unread (if (fd-stream-unread stream
)
2193 (setf (fd-stream-unread stream
) nil
)
2194 (let ((ibuf (fd-stream-ibuf stream
)))
2196 (let ((head (buffer-head ibuf
))
2197 (tail (buffer-tail ibuf
)))
2198 (values (reset-buffer ibuf
) (- (+ unread tail
) head
)))
2199 (values nil unread
)))))
2201 (defun fd-stream-clear-input (stream)
2202 (flush-input-buffer stream
)
2203 #!+(and win32 win32-uses-file-handles
)
2205 (sb!win32
:handle-clear-input
(fd-stream-fd stream
))
2206 (setf (fd-stream-listen stream
) nil
))
2207 #!+(and win32
(not win32-uses-file-handles
))
2210 (sb!win32
:fd-clear-input
(fd-stream-fd stream
))
2211 (setf (fd-stream-listen stream
) nil
))
2213 (catch 'eof-input-catcher
2214 (loop until
(sysread-may-block-p stream
)
2216 (refill-input-buffer stream
)
2217 (reset-buffer (fd-stream-ibuf stream
)))
2220 ;;; Handle miscellaneous operations on FD-STREAM.
2221 (defun fd-stream-misc-routine (fd-stream operation
&optional arg1 arg2
)
2222 (declare (ignore arg2
))
2225 (labels ((do-listen ()
2226 (let ((ibuf (fd-stream-ibuf fd-stream
)))
2227 (or (not (eql (buffer-head ibuf
) (buffer-tail ibuf
)))
2228 (fd-stream-listen fd-stream
)
2230 (sb!win32
:fd-listen
(fd-stream-fd fd-stream
))
2232 ;; If the read can block, LISTEN will certainly return NIL.
2233 (if (sysread-may-block-p fd-stream
)
2235 ;; Otherwise select(2) and CL:LISTEN have slightly
2236 ;; different semantics. The former returns that an FD
2237 ;; is readable when a read operation wouldn't block.
2238 ;; That includes EOF. However, LISTEN must return NIL
2240 (progn (catch 'eof-input-catcher
2241 ;; r-b/f too calls select, but it shouldn't
2242 ;; block as long as read can return once w/o
2244 (refill-input-buffer fd-stream
))
2245 ;; At this point either IBUF-HEAD != IBUF-TAIL
2246 ;; and FD-STREAM-LISTEN is NIL, in which case
2247 ;; we should return T, or IBUF-HEAD ==
2248 ;; IBUF-TAIL and FD-STREAM-LISTEN is :EOF, in
2249 ;; which case we should return :EOF for this
2250 ;; call and all future LISTEN call on this stream.
2251 ;; Call ourselves again to determine which case
2256 (setf (fd-stream-unread fd-stream
) arg1
)
2257 (setf (fd-stream-listen fd-stream
) t
))
2259 (when (open-stream-p fd-stream
)
2260 (finish-fd-stream-output fd-stream
)
2261 (release-fd-stream-resources fd-stream
)
2262 (do-after-close-actions fd-stream arg1
)))
2264 (fd-stream-clear-input fd-stream
))
2266 (flush-output-buffer fd-stream
))
2268 (finish-fd-stream-output fd-stream
))
2270 (fd-stream-element-type fd-stream
))
2272 (fd-stream-external-format fd-stream
))
2274 (= 1 (the (member 0 1)
2275 (sb!unix
:unix-isatty
(fd-stream-fd fd-stream
)))))
2279 (fd-stream-char-pos fd-stream
))
2281 (unless (stream-pathname fd-stream
)
2282 ;; This is a TYPE-ERROR because ANSI's species FILE-LENGTH
2283 ;; "should signal an error of type TYPE-ERROR if stream is not
2284 ;; a stream associated with a file". Too bad there's no very
2285 ;; appropriate value for the EXPECTED-TYPE slot..
2286 (error 'simple-type-error
2288 :expected-type
'file-stream
2289 :format-control
"~S is not a stream associated with a file."
2290 :format-arguments
(list fd-stream
)))
2291 ;; OS-FILE-LENGTH wraps fstat() and GetFileSize(), both of which
2292 ;; can return NIL and an errno. Since ANSI says we're to return
2293 ;; NIL if the length cannot be determined, we just return the
2294 ;; first value. (Before 1.0.15 or so, we errored when fstat()
2296 (truncate (os-file-length (fd-stream-fd fd-stream
))
2297 (fd-stream-element-size fd-stream
)))
2298 (:file-string-length
2300 (character (fd-stream-character-size fd-stream arg1
))
2301 (string (fd-stream-string-size fd-stream arg1
))))
2304 (fd-stream-set-file-position fd-stream arg1
)
2305 (fd-stream-get-file-position fd-stream
)))))
2307 ;; FIXME: Think about this.
2309 ;; (defun finish-fd-stream-output (fd-stream)
2310 ;; (let ((timeout (fd-stream-timeout fd-stream)))
2311 ;; (loop while (fd-stream-output-queue fd-stream)
2312 ;; ;; FIXME: SIGINT while waiting for a timeout will
2313 ;; ;; cause a timeout here.
2314 ;; do (when (and (not (serve-event timeout)) timeout)
2315 ;; (signal-timeout 'io-timeout
2316 ;; :stream fd-stream
2317 ;; :direction :write
2318 ;; :seconds timeout)))))
2320 (defun finish-fd-stream-output (stream)
2321 (flush-output-buffer stream
)
2323 ((null (fd-stream-output-queue stream
)))
2324 (serve-all-events)))
2326 (defun fd-stream-get-file-position (stream)
2327 (declare (fd-stream stream
))
2329 (let ((posn (os-seek (fd-stream-fd stream
) 0 t
)))
2330 (declare (type (or (alien sb
!unix
:off-t
) null
) posn
))
2331 ;; We used to return NIL for errno==ESPIPE, and signal an error
2332 ;; in other failure cases. However, CLHS says to return NIL if
2333 ;; the position cannot be determined -- so that's what we do.
2334 (when (integerp posn
)
2335 ;; Adjust for buffered output: If there is any output
2336 ;; buffered, the *real* file position will be larger
2337 ;; than reported by lseek() because lseek() obviously
2338 ;; cannot take into account output we have not sent
2340 (dolist (buffer (fd-stream-output-queue stream
))
2341 (incf posn
(- (buffer-tail buffer
) (buffer-head buffer
))))
2342 (let ((obuf (fd-stream-obuf stream
)))
2344 (incf posn
(buffer-tail obuf
))))
2345 ;; Adjust for unread input: If there is any input
2346 ;; read from UNIX but not supplied to the user of the
2347 ;; stream, the *real* file position will smaller than
2348 ;; reported, because we want to look like the unread
2349 ;; stuff is still available.
2350 (let ((ibuf (fd-stream-ibuf stream
)))
2352 (decf posn
(- (buffer-tail ibuf
) (buffer-head ibuf
)))))
2353 (when (fd-stream-unread stream
)
2355 ;; Divide bytes by element size.
2356 (truncate posn
(fd-stream-element-size stream
))))))
2358 (defun fd-stream-set-file-position (stream position-spec
)
2359 (declare (fd-stream stream
))
2360 (check-type position-spec
2361 (or (alien sb
!unix
:off-t
) (member nil
:start
:end
))
2362 "valid file position designator")
2365 ;; Make sure we don't have any output pending, because if we
2366 ;; move the file pointer before writing this stuff, it will be
2367 ;; written in the wrong location.
2368 (finish-fd-stream-output stream
)
2369 ;; Disable interrupts so that interrupt handlers doing output
2372 (unless (fd-stream-output-finished-p stream
)
2373 ;; We got interrupted and more output came our way during
2374 ;; the interrupt. Wrapping the FINISH-FD-STREAM-OUTPUT in
2375 ;; WITHOUT-INTERRUPTS gets nasty as it can signal errors,
2376 ;; so we prefer to do things like this...
2378 ;; Clear out any pending input to force the next read to go to
2380 (flush-input-buffer stream
)
2381 ;; Trash cached value for listen, so that we check next time.
2382 (setf (fd-stream-listen stream
) nil
)
2384 (multiple-value-bind (offset origin
)
2391 (values (* position-spec
(fd-stream-element-size stream
))
2393 (declare (type (alien sb
!unix
:off-t
) offset
))
2394 (let ((posn (os-seek (fd-stream-fd stream
) offset origin
)))
2395 ;; CLHS says to return true if the file-position was set
2396 ;; succesfully, and NIL otherwise. We are to signal an error
2397 ;; only if the given position was out of bounds, and that is
2398 ;; dealt with above. In times past we used to return NIL for
2399 ;; errno==ESPIPE, and signal an error in other cases.
2401 ;; FIXME: We are still liable to signal an error if flushing
2403 (return-from fd-stream-set-file-position
2404 (typep posn
'(alien sb
!unix
:off-t
))))))))
2409 ;;; Create a stream for the given Unix file descriptor.
2411 ;;; If INPUT is non-NIL, allow input operations. If OUTPUT is non-nil,
2412 ;;; allow output operations. If neither INPUT nor OUTPUT is specified,
2413 ;;; default to allowing input.
2415 ;;; ELEMENT-TYPE indicates the element type to use (as for OPEN).
2417 ;;; BUFFERING indicates the kind of buffering to use.
2419 ;;; TIMEOUT (if true) is the number of seconds to wait for input. If
2420 ;;; NIL (the default), then wait forever. When we time out, we signal
2422 (defun make-fd-stream (fd
2425 (output nil output-p
)
2426 (element-type 'base-char
)
2428 (external-format :default
)
2440 (format nil
"file ~A" file
)
2441 (format nil
"descriptor ~W" fd
))))
2442 (declare (type index fd
) (type (or real null
) timeout
)
2443 (type (member :none
:line
:full
) buffering
))
2444 (cond ((not (or input-p output-p
))
2446 ((not (or input output
))
2447 (error "File descriptor must be opened either for input or output.")))
2448 (let ((stream (%make-fd-stream
:fd fd
2449 :buffering buffering
2450 :dual-channel-p dual-channel-p
2451 :external-format external-format
2452 :char-size
(external-format-char-size external-format
)
2455 (coerce timeout
'single-float
)
2460 :after-close after-close
2463 (set-fd-stream-routines stream element-type external-format
2464 input output input-buffer-p
)
2465 (when (and auto-close
(fboundp 'finalize
))
2468 ;; FIXME: CLOSE-DESCRIPTOR takes care of EINTR, but
2469 ;; should we signal an error for other close()
2470 ;; failures here? I don't know what consequences
2471 ;; follow from signalling error during GC. But if
2472 ;; close() fails, we really shouldn't lose track of
2474 (close-descriptor fd
)
2476 (format *terminal-io
* "** closed file descriptor ~W **~%"
2481 ;;; Since SUSv3 mkstemp() doesn't specify the mode of the created file
2482 ;;; and since we have to implement most of this ourselves for Windows
2483 ;;; anyway, it seems worthwhile to depart from the mkstemp()
2484 ;;; specification by taking a mode to use when creating the new file.
2485 ;;; This was introduced around 1.0.13, was a thin wrapper around a
2486 ;;; routine in the runtime, and was used in only a very restricted
2487 ;;; way; before 1.0.15, I noticed that there were some drawbacks in
2488 ;;; the C library routines in that routine in the runtime that limited
2489 ;;; the general-purposeness of that routine, and so rewrote it all in
2490 ;;; Lisp; doing it in Lisp also means that the user can control the
2491 ;;; randomness manually, if necessary.
2492 (defvar *random-filename-random-state
* nil
2493 "Random-state used when creating random filenames. SETF-able,
2494 if you want to produce a predictable sequence of filenames. If
2495 NIL, generating the next random filename will assign this
2496 variable a new, randomly generated random-state.")
2498 (defun random-filename (template-string)
2499 (unless *random-filename-random-state
*
2500 (setf *random-filename-random-state
* (make-random-state t
)))
2501 (let* (;; mkstemp() uses POSIX's so-called "portable filename
2502 ;; character set" for filling the template. We exclude #\.,
2503 ;; since that's our pathname type separator.
2504 (random-charset #.
(format nil
"~@{~A~}"
2505 "abcdefghijklmnopqrstuvwxyz"
2506 "ABCDEFGHIJKLMNOPQRSTUVWXYZ"
2508 (X-pos (1+ (position #\X template-string
:test
'char
/= :from-end t
)))
2509 (template-length (- (length template-string
) X-pos
))
2510 (template-stem (subseq template-string
0 X-pos
)))
2511 (unless (>= template-length
6)
2512 (error "bad mkstemp template ~A" template-string
))
2513 (let ((random-suffix (loop
2514 repeat template-length
2518 64 *random-filename-random-state
*)))))
2519 (concatenate 'string template-stem random-suffix
))))
2523 ;; Circa 1.0.14, the innards of OPEN have been entirely rewritten from
2524 ;; the CMU code, with a few goals in mind: (1) to be usable as a
2525 ;; substrate for more than one streams API, to prevent functionality
2526 ;; skew; (2) to be asynch-interrupt-safe and slightly less prone to
2527 ;; breakage due to fork(), (3) to try to do as much as possible using
2528 ;; Lisp-level file system functions, rather than raw Unix system
2529 ;; calls, so that we have some stress-testing on that code, so that we
2530 ;; get consistent, Lisp-level error detection and reporting when
2531 ;; things go awry, and since some of the system calls' behaviors vary
2532 ;; a bit across Unix and Windows.
2534 ;; When we construct a stream, we store a function to be called during
2535 ;; CLOSE, and also a PID. This routine runs the close-time code,
2536 ;; after the descriptor is closed, in case this process is responsible
2538 (defun do-after-close-actions (stream abortp
)
2539 (when (and #!+unix
(eql (sb!unix
:unix-getpid
) (stream-owner-pid stream
))
2540 (stream-after-close stream
))
2541 (with-simple-restart (continue "Continue, leaving files in place.")
2542 (funcall (stream-after-close stream
) stream abortp
))
2543 (setf (stream-after-close stream
) nil
)))
2545 ;; We have separate functions for actions to be performed after
2546 ;; constructing the stream, but before returning it to the user. The
2547 ;; only one that's common to all ways of building SBCL is the one that
2548 ;; repositions the file pointer after constructing the stream.
2549 (defun open-if-exists-append (stream)
2550 (file-position stream
:end
))
2552 (defvar *open-backup-suffix
* ".bak"
2553 "Backup suffix used when opening with :RENAME.")
2555 (defun open-backup-pathname (pathname)
2556 "Return the name that a file whose truename is PATHNAME will have
2557 after a successful :RENAME opening. Note that this is a syntactic
2558 operation, and does not examine the file system; if PATHNAME names a
2559 symlink, calling OPEN on PATHNAME with IF-EXISTS :RENAME will rename a
2560 file whose truename is not PATHNAME."
2561 (parse-native-namestring
2562 (concatenate 'string
(native-namestring pathname
) *open-backup-suffix
*)
2563 (pathname-host pathname
)))
2565 (defun close-abort-delete (stream abortp
)
2566 "During an aborting close, delete the file associated with the
2569 (delete-file (stream-truename stream
))))
2571 (defun make-deleted-file-closer (stream)
2572 (let ((old-after-close (stream-after-close stream
)))
2573 (lambda (stream abort
)
2574 (declare (ignore abort
))
2575 (if (member old-after-close
2576 #!+open-lazy-file-disposition
2577 '(#'close-lazy-supersede
#'close-lazy-rename
)
2578 #!-open-lazy-file-disposition
2579 '(#'close-delete-altname
#'close-rename-altname
))
2580 (funcall old-after-close stream t
)
2581 (delete-file (stream-truename stream
))))))
2583 ;; NTFS supports hard links, and some Unixes can mount file systems
2584 ;; that don't (e.g., FAT). So try linking first on both Unix and
2585 ;; Windows, and then fail over to renaming.
2586 (defun make-temporary-name-for-file (pathname)
2587 "Link or rename PATHNAME to a random name in the same
2588 directory. If file does not exist, returns NIL. Otherwise,
2589 returns the random name and a boolean that's true in case the
2590 file was renamed, rather than linked."
2591 (loop with filename
= (native-namestring pathname
)
2592 for temppath
= (parse-native-namestring
2594 (concatenate 'string filename
"-XXXXXX"))
2595 (pathname-host pathname
))
2596 thereis
(handler-case (link-file pathname temppath
)
2597 (file-does-not-exist () (return nil
))
2598 (file-exists () nil
)
2601 (replace-file pathname temppath
)))
2602 (values new-name t
))))))
2604 ;; FIXME: rewrite this, to make it clearer that this is
2605 ;; transaction-like?
2606 (defmacro with-temporary-name-for-file
((var pathname
) &body body
)
2607 "Run BODY with VAR bound to a new, randomly selected name for
2608 the file named by PATHNAME. If control leaves body abnormally,
2609 try to restore FILE to its old name. Otherwise, the file named
2610 by PATHNAME at the start of BODY will be named by the value of
2611 VAR after the body."
2612 (with-unique-names (oldname renamedp
)
2613 `(let ((,oldname
,pathname
))
2614 (multiple-value-bind (,var
,renamedp
)
2615 (make-temporary-name-for-file ,oldname
)
2617 (multiple-value-prog1 (progn ,@body
) (setf ,var nil
))
2620 (rename-file ,var
,oldname
)
2621 (delete-file ,var
))))))))
2623 ;; The actions to conduct at OPEN- and CLOSE-time differ slightly in
2624 ;; the lazy/non-lazy file disposition worlds. In fact, the same basic
2625 ;; things happen, just at different times.
2626 #!-open-lazy-file-disposition
2628 (defun open-eager-rename (stream)
2629 "For openings that create a file with mkstemp(), rename the new
2630 file to have its final name before returning a stream to the
2631 user, and modify the stream so that a previously existing file
2632 gets renamed or deleted at CLOSE-time."
2633 (with-temporary-name-for-file (temp-name (stream-altname stream
))
2634 (rename-file (stream-truename stream
)
2635 (merge-pathnames (stream-altname stream
)
2636 (make-pathname :type
:unspecific
)))
2637 (setf (stream-truename stream
) (stream-altname stream
)
2638 (stream-altname stream
) temp-name
)))
2640 (defun close-rename-altname (stream abortp
)
2641 "When closing a stream opened with IF-EXISTS :RENAME either
2642 restore or rename the file that existed before the stream was
2645 ;; FIXME: Win32's MoveFileEx can atomically rename files. I
2646 ;; don't know whether that's how RENAME-FILE should be
2647 ;; implemented, but we can use it here, in any case.
2648 #+win32
(delete-file (stream-truename stream
))
2649 (rename-file (stream-altname stream
) (stream-truename stream
))
2650 (return-from close-rename-altname
))
2651 (rename-file (stream-altname stream
)
2652 (merge-pathnames (open-backup-pathname
2653 (stream-truename stream
))
2654 (make-pathname :type
:unspecific
))))
2656 (defun close-delete-altname (stream abortp
)
2657 "When closing a stream opened with IF-EXISTS :RENAME-AND-DELETE,
2658 either restore or delete the file that existed before the stream
2659 was opened. If SBCL was built with the
2660 feature :OPEN-SUPERSEDE-IS-RENAME-AND-DELETE, this gets called
2661 during a CLOSE of a stream opened with :SUPERSEDE, too."
2663 ;; FIXME: Win32's MoveFileEx can atomically rename files. I
2664 ;; don't know whether that's how RENAME-FILE should be
2665 ;; implemented, but we can use it here, in any case.
2666 #+win32
(delete-file (stream-truename stream
))
2667 (rename-file (stream-altname stream
) (stream-truename stream
))
2668 (return-from close-delete-altname
))
2669 (delete-file (stream-altname stream
)))
2671 (defun close-delete-pathname (stream abortp
)
2672 "During an aborting close, delete the file named by the name
2673 used to open the stream. (This behavior makes no sense, but
2674 it's what CMU/SBCL has always done for :SUPERSEDE.)"
2676 (delete-file (pathname stream
)))))
2678 ;; Note that in the :OPEN-LAZY-FILE-DISPOSITION world, an opening that
2679 ;; creates a new file doesn't touch any existing file until CLOSE-time.
2680 #!+open-lazy-file-disposition
2682 (defun close-lazy-supersede (stream abortp
)
2683 "When closing a stream opened with IF-EXISTS :RENAME-AND-DELETE,
2684 either rename the file associated with the stream into place, or
2685 delete the file associated with the stream. If SBCL was built
2686 with the feature :OPEN-SUPERSEDE-IS-RENAME-AND-DELETE, this gets
2687 called during a CLOSE of a stream opened with :SUPERSEDE, too."
2689 (delete-file (stream-truename stream
))
2690 (return-from close-lazy-supersede
))
2691 (rename-file (stream-truename stream
) (stream-altname stream
))
2692 (setf (stream-truename stream
) (stream-altname stream
)))
2694 (defun close-lazy-rename (stream abortp
)
2695 "When closing a stream opened with IF-EXISTS :RENAME-AND-DELETE,
2696 either rename the file associated with the stream into place and
2697 rename the old file to the backup name, or delete the file
2698 associated with the stream."
2700 (delete-file (stream-truename stream
))
2701 (return-from close-lazy-rename
))
2702 (let ((backup-path (merge-pathnames (open-backup-pathname
2703 (stream-altname stream
))
2704 (make-pathname :type
:unspecific
)))
2706 (with-temporary-name-for-file (temp-name (stream-altname stream
))
2707 (rename-file (stream-truename stream
) (stream-altname stream
))
2708 (setf link-path temp-name
;hold onto TEMP-NAME for use below.
2709 (stream-truename stream
) (stream-altname stream
)))
2710 ;; We do this final rename outside of
2711 ;; WITH-TEMPORARY-NAME-FOR-FILE so that if it fails, no data
2712 ;; will have been lost (though the old file will be left with a
2713 ;; random name if the user aborts).
2715 (rename-file link-path backup-path
)))))
2717 (defun open-element-type-satisfies-function (type)
2718 (or (member type
'(:default unsigned-byte signed-byte
))
2719 (subtypep type
'character
)
2720 ;; XXX: this should be a /finite/ subtype of integer, but I
2721 ;; don't know if we are able to say that.
2722 (subtypep type
'integer
)))
2724 ;; I think this macro captures the common aspect of calling a
2725 ;; VALUES-FORM that returns values that include something that must
2726 ;; not be allowed to leak. FIXME: some other places could perhaps
2727 ;; take advantage of this (e.g., the temporary file descriptor used in
2729 (defmacro uninterruptibly-bind-and-protect
2730 ((&rest vars
) values-form form
&body cleanup-forms
)
2731 "Bind VARS to the return values of VALUES-FORM, evaluate FORM
2732 and then CLEANUP-FORMS with VARS so bound; CLEANUP-FORMS will be
2733 run even if control transfers out of FORM abnormally.
2734 Asynchronous interrupts are enabled during FORM, and nowhere
2736 `(without-interrupts
2737 (multiple-value-bind ,vars
,values-form
2739 (with-local-interrupts ,form
)
2742 ;; The following function, OPEN-FILE, is a high-level internal
2743 ;; primitive that's meant to do all the work of OPEN except for
2744 ;; constructing a stream. It's designed to suit the needs of
2745 ;; FD-STREAMS and SB-SIMPLE-STREAMS, but should also suffice for other
2746 ;; ways of implementing ANSI FILE-STREAMs.
2748 ;; Note: as far as I can tell, any call to a function that returns a
2749 ;; file descriptor while interrupts are enabled exposes a window
2750 ;; during which an asynchronous interrupt can lead to fd leak. So
2751 ;; while OPEN-FILE must disable interrupts around open() calls, we
2752 ;; don't want to its callers to have to disable interrupts around
2753 ;; OPEN-FILE, since OPEN-FILE must do various other error-prone things
2754 ;; (e.g., resolving truenames). So in order to allow our callers to
2755 ;; be ignorant of asynchronous interrupt concerns, we don't have
2756 ;; OPEN-FILE return a descriptor, but instead have it assign a special
2757 ;; variable as described in the docstring.
2759 (filespec direction if-does-not-exist if-exists element-type
2761 "Open a file according to OPEN-like arguments. FILESPEC is the
2762 verbatim (unmerged, untranslated) argument to OPEN. DIRECTION
2763 and ELEMENT-TYPE are the arguments supplied to or defaulted in
2764 OPEN. IF-DOES-NOT-EXIST and IF-EXISTS are the arguments
2765 supplied to OPEN, or the symbol SB-IMPL::DEFAULT if the
2766 argument was not supplied. OS-OPEN-ARGS is an
2767 OS-OPEN-ARGUMENTS list, containing any extra arguments to be
2768 passed down to the system's open syscall.
2770 Callers must bind *FILE-DESCRIPTOR* in the dynamic
2771 environment. If OPEN-FILE succeeds, it sets *FILE-DESCRIPTOR*
2772 to an integer, and returns seven values to be used in the
2775 1. the result of merging FILESPEC,
2777 2. the name of the file actually open,
2779 3. a pathname or NIL, used as bookkeeping for some kinds of
2782 4. a boolean that's true if the stream is for input,
2784 5. a boolean that's true if the stream is for output,
2786 6. a function of one argument to call on the to-be-created
2787 stream before returning it to the user,
2789 7. a function of two arguments to be called after closing the
2790 descriptor during CLOSE; the first argument to this
2791 function is the stream, the second a generalized boolean
2792 that's true in case the stream is being closed in an
2795 The caller is responsible for constructing a stream, calling
2796 the first function, and arranging for the second function to
2797 be called during CLOSE.
2799 If OPEN-FILE does not open a file, either because IF-EXISTS
2800 and IF-DOES-NOT-EXIST inhibit opening or because of file
2801 system errors during open(), OPEN-FILE will return NIL or
2802 signal a FILE-ERROR, as determined by the arguments and file
2805 If OPEN-FILE signals an error or returns NIL,
2806 *FILE-DESCRIPTOR* will have the value NIL after control
2807 returns from OPEN-FILE.
2809 If any error occurs after a file has been opened, OPEN-FILE
2810 will close the descriptor.
2812 Note that OPEN-FILE can signal FILE-ERRORs not directly
2813 related to a call to open(): truename resolution, pathname
2814 unparsing, logical pathname translation, etc. can all error."
2815 (declare (type (member :input
:output
:io
:probe
) direction
))
2816 (declare (type (satisfies open-element-type-satisfies-function
)
2818 (declare (ignore element-type
))
2820 ;; This is our internal protocol.
2821 (unless (boundp '*file-descriptor
*)
2822 (bug "*FILE-DESCRIPTOR* is not bound at start of OPEN-FILE."))
2824 ;; Basic sanity stuff first. Should be straightforward
2825 ;; transcriptions of things from the CLHS.
2826 (setf filespec
(pathname filespec
))
2827 (when (wild-pathname-p filespec
)
2828 (error 'simple-file-error
2830 :format-control
"can't open a wild pathname: ~A"
2831 :format-arguments
(list filespec
)))
2832 (when (eq if-exists
'default
)
2833 (if (member direction
'(:output
:io
))
2834 (setf if-exists
(if (eq (pathname-version filespec
) :newest
)
2837 (setf if-exists nil
)))
2838 (when (eq if-does-not-exist
'default
)
2839 (setf if-does-not-exist
2841 ((eq direction
:probe
)
2843 ((or (eq direction
:input
)
2844 (member if-exists
'(:overwrite
:append
2845 #!+cdr-5
:truncate
)))
2847 ((and (member direction
'(:output
:io
))
2848 (not (member if-exists
'(:overwrite
:append
2849 #!+cdr-5
:truncate
))))
2851 (check-type if-does-not-exist
(member :create
:error nil
))
2852 (check-type if-exists
(member :new-version
:supersede
2853 :rename
:rename-and-delete
2856 #!+cdr-5
:truncate
))
2858 (labels ((fail (errno)
2859 (simple-file-perror "cannot open ~A" filespec errno
))
2860 (fail-if (boolean errno
)
2863 (return-from open-file nil
)))
2864 (open-bug (existsp) ;This hasn't happened yet, in fact.
2865 (bug "~&This can't happen. ~
2866 The file does~:[ not~;~] exist.~%
2868 IF-DOES-NOT-EXIST: ~A~%~
2870 existsp direction if-does-not-exist if-exists
))
2871 (compute-os-open-arguments (existsp)
2872 "Using the defaulted arguments to OPEN-FILE in the
2873 lexical environment and a boolean that's true if
2874 and only if the file exists, compute the arguments
2875 to the OS's opening syscall."
2876 ;; Remember that IF-EXISTS actions are to be carried out
2877 ;; only when the file already exists, so, e.g., :I-D-N-E
2878 ;; :CREATE :I-E :APPEND doesn't get :APPEND's special
2879 ;; treatment if the file doesn't yet exist. Note also
2880 ;; that because we determine whether the file exists
2881 ;; before calling this, this code only gets run in case
2882 ;; we actually try opening something, e.g., we don't run
2883 ;; this when the file does not exist and
2884 ;; IF-DOES-NOT-EXIST is NIL or :ERROR.
2885 (merge-os-open-arguments
2886 #!-win32-uses-file-handles
2887 (%make-os-open-arguments
2890 (:input sb
!unix
:o_rdonly
)
2891 (:probe sb
!unix
:o_rdonly
)
2892 (:output sb
!unix
:o_wronly
)
2893 (:io sb
!unix
:o_rdwr
))
2895 (if (member direction
'(:output
:io
))
2897 (:append sb
!unix
:o_append
)
2898 ((:rename
:rename-and-delete
)
2899 (logior sb
!unix
:o_creat sb
!unix
:o_excl
))
2901 #!+open-supersede-is-rename-and-delete
2902 (logior sb
!unix
:o_creat sb
!unix
:o_excl
)
2903 #!-open-supersede-is-rename-and-delete
2906 (:truncate sb
!unix
:o_trunc
)
2909 (if (eq if-does-not-exist
:create
)
2910 (logior sb
!unix
:o_creat sb
!unix
:o_excl
)
2912 ;; Win32's CreateFile seems to be able to do all the
2913 ;; basic stuff that we have POSIX open() do; it just
2914 ;; organizes the details differently.
2915 #!+win32-uses-file-handles
2916 (%make-os-open-arguments
2919 (:input sb
!win32
:generic_read
)
2921 (:output
(if (and existsp
(eq if-exists
:append
))
2922 (logandc2 sb
!win32
:generic_write
2923 sb
!win32
:file_write_data
)
2924 sb
!win32
:generic_write
))
2925 (:io
(logior sb
!win32
:generic_read
2926 (if (and existsp
(eq if-exists
:append
))
2927 (logandc2 sb
!win32
:generic_write
2928 sb
!win32
:file_write_data
)
2929 sb
!win32
:generic_write
))))
2930 :creation-disposition
2932 (if (member direction
'(:output
:io
))
2934 ((:overwrite
:append
) sb
!win32
:open_existing
)
2935 ((:rename
:rename-and-delete
)
2936 sb
!win32
:create_new
)
2937 #!-open-supersede-is-rename-and-delete
2938 (:supersede sb
!win32
:truncate_existing
)
2939 #!+open-supersede-is-rename-and-delete
2940 (:supersede sb
!win32
:create_new
)
2942 (:truncate sb
!win32
:truncate_existing
))
2943 sb
!win32
:open_existing
)
2944 (if (eq if-does-not-exist
:create
)
2948 (random-pathname (pathname)
2949 (parse-native-namestring
2951 (concatenate 'string
(native-namestring pathname
) "-XXXXXX"))
2952 (pathname-host pathname
)))
2953 (ensure-extant-nondirectory-file (truename)
2954 (multiple-value-bind (targetp errno ino mode
)
2955 (sb!unix
:unix-stat
(native-namestring truename
))
2956 (declare (ignore ino
))
2959 (when (= (logand mode sb
!unix
:s-ifmt
) sb
!unix
:s-ifdir
)
2960 (fail sb
!unix
:eisdir
))))
2961 (%open
(truename os-open-arguments
)
2962 (locally (declare (special *file-descriptor
*))
2963 (setf *file-descriptor
* nil
)
2964 (let ((filename (native-namestring truename
)))
2965 (uninterruptibly-bind-and-protect (file-descriptor errno
)
2966 (os-open filename os-open-arguments
)
2969 (setf *file-descriptor
* file-descriptor
2970 file-descriptor nil
)
2974 (when file-descriptor
2975 (close-descriptor file-descriptor t
)
2976 (setf *file-descriptor
* nil
)
2977 #|
(when (eq if-does-not-exist
:create
)
2978 (delete-file truename
))|
#)))))
2980 (let ((pathname (merge-pathnames filespec
)))
2981 (if (eq (car (pathname-directory pathname
)) :absolute
)
2983 (if (typep pathname
'logical-pathname
)
2984 ;; Relative logical pathnames can, in principle,
2985 ;; have translations (though programmers who
2986 ;; write programs that rely on such translations
2987 ;; would steal sheep).
2989 ;; Note that getcwd(3) can fail on traditional
2990 ;; Unices. In that case, we can't get a full
2991 ;; pathname for the user, even if we can open the
2993 (let ((cwd (ignore-errors
2994 #!+unix
(sb!unix
:posix-getcwd
)
2995 #!+win32
(sb!win32
:get-current-directory
)))
2996 (host (pathname-host filespec
)))
2999 (parse-native-namestring
3000 cwd host nil
:as-directory t
)))
3001 (merge-pathnames pathname cwd-pathname
))
3004 (not (not (member direction
'(:input
:probe
:io
)))))
3006 (not (not (member direction
'(:io
:output
)))))
3007 (create-beside (truename os-open-arguments
)
3008 (loop for random-pathname
= (random-pathname truename
)
3010 (%open random-pathname os-open-arguments
)
3011 (file-exists () nil
))
3014 (merged-pathname) random-pathname
3015 ;; For files created under a random
3016 ;; name, eventually call RENAME-FILE,
3017 ;; which implicitly merges. So we
3018 ;; reparse the unparsed TRUENAME in
3019 ;; order to normalize pathnames like
3020 ;; #S(pathname :name "abc.def" :type
3021 ;; nil), which will rename wrong with
3022 ;; the parse of "abc.def-XXXXXX".
3023 (parse-native-namestring
3024 (native-namestring truename
)
3025 (pathname-host truename
))
3026 (input-p) (output-p)
3027 (if (eq direction
:probe
) #'close
3028 #!-open-lazy-file-disposition
3029 #'open-eager-rename
)
3030 ;; Note: if :NEW-VERSION is ever
3031 ;; changed to create a new file when
3032 ;; one already exists, decide whether
3033 ;; it should be like :RENAME or
3034 ;; :RENAME-AND-DELETE, and then
3035 ;; change both these two forms.
3036 #!-open-lazy-file-disposition
3037 (if (eq if-exists
:rename
)
3038 #'close-rename-altname
3039 #'close-delete-altname
)
3040 #!+open-lazy-file-disposition
3041 (if (eq if-exists
:rename
)
3043 #'close-lazy-supersede
)))))
3044 (open-extant (truename os-open-arguments
)
3045 (when (%open truename os-open-arguments
)
3046 (values (merged-pathname) truename nil
3047 (input-p) (output-p)
3048 (cond ((eq direction
:probe
) #'close
)
3049 ((and (member direction
'(:output
:io
))
3050 (eq if-exists
:append
))
3051 #'open-if-exists-append
))
3052 ;; Bizarre, unnecessary
3053 ;; historical behavior.
3054 #|
#!-open-supersede-is-rename-and-delete
3055 (if (and (member direction
'(:output
:io
))
3056 (eq if-exists
:supersede
))
3057 #'close-delete-pathname
)|
#)))
3058 #!-open-lazy-file-disposition
3059 (create-in-place (truename os-open-arguments
)
3060 (when (%open truename os-open-arguments
)
3061 (values (merged-pathname) truename nil
3062 (input-p) (output-p)
3063 (if (eq direction
:probe
) #'close
)
3064 #'close-abort-delete
)))
3065 ;; On Windows, we can't generally rename a file while it's
3066 ;; open, so we ensure an existing file is out of the way
3067 ;; and create in place.
3068 #!+(and win32
(not open-lazy-file-disposition
))
3069 (win32-lossy-create-beside (truename os-open-arguments
)
3070 (with-temporary-name-for-file (temp-name truename
)
3071 (ignore-errors (delete-file truename
))
3072 (when (%open truename os-open-arguments
)
3073 (values (merged-pathname) truename temp-name
3074 (input-p) (output-p)
3075 nil
(if (eq if-exists
:rename
)
3076 #'close-rename-altname
3077 #'close-delete-altname
))))))
3078 (let* ((truename (handler-case (probe-file filespec
)
3080 (if (eq if-does-not-exist nil
)
3081 (return-from open-file nil
)
3084 ;; We know the file exists.
3085 (cond ((or (member direction
'(:input
:probe
))
3087 '(:overwrite
:append
3089 #!-open-supersede-is-rename-and-delete
3091 (open-extant truename
(compute-os-open-arguments t
)))
3092 ((and (member direction
'(:output
:io
))
3094 '(:rename
:rename-and-delete
3095 #!+open-supersede-is-rename-and-delete
3097 (ensure-extant-nondirectory-file truename
)
3098 #!-
(and win32
(not open-lazy-file-disposition
))
3099 (create-beside truename
(compute-os-open-arguments t
))
3100 #!+(and win32
(not open-lazy-file-disposition
))
3101 (win32-lossy-create-beside
3102 truename
(compute-os-open-arguments t
)))
3103 ((and (member direction
'(:output
:io
))
3104 (member if-exists
'(:error nil
:new-version
)))
3105 (fail-if (member if-exists
'(:error
:new-version
))
3106 #!-win32-uses-file-handles
3108 #!+win32-uses-file-handles
3109 sb
!win32
:error_file_exists
))
3111 (let ((truename (translate-logical-pathname
3112 (merge-pathnames filespec
))))
3113 (cond ((eq if-does-not-exist
:create
)
3114 #!-open-lazy-file-disposition
3116 truename
(compute-os-open-arguments nil
))
3117 #!+open-lazy-file-disposition
3118 (create-beside truename
(compute-os-open-arguments nil
)))
3119 ((member if-does-not-exist
'(:error nil
))
3120 (fail-if (eq if-does-not-exist
:error
) sb
!unix
:enoent
))
3121 (t (open-bug nil
))))))))
3123 (defun open (pathspec &rest keys
3125 (direction :input
) (element-type 'character
)
3126 (if-exists nil if-exists-supplied-p
)
3127 (if-does-not-exist nil if-does-not-exist-supplied-p
)
3128 (external-format :default
))
3132 "Return a stream which reads from or writes to PATHSPEC.
3134 :DIRECTION - one of :INPUT, :OUTPUT, :IO, or :PROBE
3135 :ELEMENT-TYPE - the type of object to read or write, default BASE-CHAR
3136 :IF-EXISTS - one of :ERROR, :NEW-VERSION, :RENAME, :RENAME-AND-DELETE,
3137 :SUPERSEDE, :OVERWRITE, :APPEND, "
3138 #!+cdr-5
":TRUNCATE "
3140 :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or NIL."
3141 ;; FIXME: document things in the manual.
3142 #+nil
" See the manual for details.")
3143 (let (*file-descriptor
*) ;OPEN-FILE sets this.
3144 (declare (special *file-descriptor
*))
3145 (multiple-value-bind (pathname truename altname
3146 input output init-func close-func
)
3150 (if if-does-not-exist-supplied-p if-does-not-exist
'default
)
3151 (if if-exists-supplied-p if-exists
'default
)
3152 ;; Unix doesn't care about the element type, but Windows
3155 ;; We extract keyword arguments this way in order to force
3156 ;; the user to say :ALLOW-OTHER-KEYS T to take advantage of
3158 (apply #'make-os-open-arguments keys
))
3160 (when *file-descriptor
*
3161 (let ((stream (make-fd-stream *file-descriptor
*
3164 :element-type element-type
3165 :external-format external-format
3171 :after-close close-func
3173 ;; Now that the descriptor is stored in the stream,
3174 ;; CLOSE and the stream finalizer are responsible for
3175 ;; closing the descriptor.
3176 (setf *file-descriptor
* nil
)
3178 (handler-case (funcall init-func stream
)
3179 ;; If the INIT-FUNC fails (e.g., if the user tries an
3180 ;; :APPEND opening on an unseekable file), close the
3181 ;; stream now, rather than waiting until GC.
3183 (close stream
:abort t
)
3186 (when *file-descriptor
*
3187 (close-descriptor *file-descriptor
* t
))))))
3189 ;; SB-SIMPLE-STREAMS wants a hook for opening an FD-STREAM, but it
3190 ;; redefines OPEN, so rather than have it duplicate the above, we'll
3191 ;; give it this. Also, any other internal stuff that needs to get an
3192 ;; FD-STREAM with OPEN-like interface can use this.
3193 (setf (fdefinition 'open-fd-stream
) #'open
)
3195 ;; RUN-PROGRAM needs to create pipes, so ISTM to be better to hide the
3196 ;; differences between descriptors and handles here.
3197 (defun open-pipe (&key
(external-format :default
))
3198 (uninterruptibly-bind-and-protect (read/nil write
/errno
)
3199 #!-win32-uses-file-handles
3201 #!+win32-uses-file-handles
3202 (sb!win32
:create-pipe
3203 (sb!win32
:make-security-attributes nil
1) 0)
3204 ;; FIXME: this form is interruptible; do we end up returning a
3205 ;; stream that wraps a closed pipe in case of interrupt?
3207 (let (read-stream write-stream
)
3208 (setf read-stream
(make-fd-stream
3210 :name
(format nil
"input pipe ~D" read
/nil
)
3212 :element-type
:default
3213 :external-format external-format
)
3215 write-stream
(make-fd-stream
3216 write
/errno
:output t
3217 :name
(format nil
"output pipe ~D" write
/errno
)
3219 :element-type
:default
3220 :external-format external-format
)
3222 (values read-stream write-stream
))
3223 ;; FIXME: this can't be a FILE-ERROR, since there's no
3224 ;; pathname involved. STREAM-ERROR? IPC-ERROR?
3225 (error "can't create pipe: ~A"
3226 #!+win32-uses-file-handles
3227 (sb!win32
:get-last-error-message write
/errno
)
3228 #!-win32-uses-file-handles
3229 (strerror write
/errno
)))
3232 (close-descriptor read
/nil t
))
3234 (close-descriptor write
/errno t
)))))
3239 ;;; the stream connected to the controlling terminal, or NIL if there is none
3242 ;;; the stream connected to the standard input (file descriptor 0)
3245 ;;; the stream connected to the standard output (file descriptor 1)
3248 ;;; the stream connected to the standard error output (file descriptor 2)
3251 ;;; This is called when the cold load is first started up, and may also
3252 ;;; be called in an attempt to recover from nested errors.
3253 (defun stream-cold-init-or-reset ()
3255 (setf *terminal-io
* (make-synonym-stream '*tty
*))
3256 (setf *standard-output
* (make-synonym-stream '*stdout
*))
3257 (setf *standard-input
* (make-synonym-stream '*stdin
*))
3258 (setf *error-output
* (make-synonym-stream '*stderr
*))
3259 (setf *query-io
* (make-synonym-stream '*terminal-io
*))
3260 (setf *debug-io
* *query-io
*)
3261 (setf *trace-output
* *standard-output
*)
3264 (defun stream-deinit ()
3265 ;; Unbind to make sure we're not accidently dealing with it
3266 ;; before we're ready (or after we think it's been deinitialized).
3267 (with-available-buffers-lock ()
3268 (without-package-locks
3269 (makunbound '*available-buffers
*))))
3271 ;;; This is called whenever a saved core is restarted.
3272 (defun stream-reinit (&optional init-buffers-p
)
3273 (when init-buffers-p
3274 (with-available-buffers-lock ()
3275 (aver (not (boundp '*available-buffers
*)))
3276 (setf *available-buffers
* nil
)))
3277 (multiple-value-bind (stdin stdout stderr
)
3278 #!-win32-uses-file-handles
(values 0 1 2)
3279 #!+win32-uses-file-handles
(sb!win32
:get-initial-handles
)
3280 #| FIXME
: what if some of these win32 handles is invalid? |
#
3281 (/primitive-print
"/got handles")
3285 (with-output-to-string (*error-output
*)
3288 stdin
:name
"standard input" :input t
:buffering
:line
3289 #!+win32
:external-format
3290 #!+win32
(sb!win32
::console-input-codepage
)))
3293 stdout
:name
"standard output" :output t
:buffering
:line
3294 #!+win32
:external-format
3295 #!+win32
(sb!win32
::console-output-codepage
)))
3298 stderr
:name
"standard error" :output t
:buffering
:line
3299 #!+win32
:external-format
3300 #!+win32
(sb!win32
::console-output-codepage
)))
3301 (/primitive-print
"/constructed *stdin*, *stdout*, *stderr*")
3302 (let* ((ttyname #.
(coerce "/dev/tty" 'simple-base-string
))
3303 (tty (sb!unix
:unix-open ttyname sb
!unix
:o_rdwr
#o666
)))
3307 :name
"the terminal"
3312 (setf *tty
* (make-two-way-stream *stdin
* *stdout
*))))
3313 (princ (get-output-stream-string *error-output
*) *stderr
*)))
3318 ;;; the Unix way to beep
3319 (defun beep (stream)
3320 (write-char (code-char bell-char-code
) stream
)
3321 (finish-output stream
))