Newer
Older
;;; **********************************************************************
;;; This code was written as part of the CMU Common Lisp project at
;;; Carnegie Mellon University, and has been placed in the public domain.
;;;
(ext:file-comment
"$Header: src/code/fd-stream.lisp $")
;;; **********************************************************************
;;;
;;; Streams for UNIX file descriptors.
;;;
;;; Written by William Lott, July 1989 - January 1990.
;;; Some tuning by Rob MacLachlan.
;;;
;;; **********************************************************************
(in-package "SYSTEM")
(intl:textdomain "cmucl")
io-timeout beep *beep-function* output-raw-bytes
*tty* *stdin* *stdout* *stderr*
binary-text-stream))
(in-package "EXTENSIONS")
(export '(*backup-extension*))
(in-package "LISP")
(export '(file-stream file-string-length))
;;;; Buffer manipulation routines.
(defvar *available-buffers* ()
"List of available buffers. Each buffer is an sap pointing to
bytes-per-buffer of memory.")
(defvar lisp::*enable-stream-buffer-p* nil)
"Number of bytes per buffer.")
;; This limit is rather arbitrary
(defconstant max-stream-element-size 1024
"The maximum supported byte size for a stream element-type.")
;;; Returns the next available buffer, creating one if necessary.
;;;
(defun next-available-buffer ()
(if *available-buffers*
(pop *available-buffers*)
(allocate-system-memory bytes-per-buffer)))
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
(declaim (inline buffer-sap bref (setf bref) buffer-copy))
(defun buffer-sap (thing &optional offset)
(declare (type simple-stream-buffer thing) (type (or fixnum null) offset)
(optimize (speed 3) (space 2) (debug 0) (safety 0)
;; Suppress the note about having to box up the return:
(ext:inhibit-warnings 3)))
(let ((sap (if (vectorp thing) (sys:vector-sap thing) thing)))
(if offset (sys:sap+ sap offset) sap)))
(defun bref (buffer index)
(declare (type simple-stream-buffer buffer)
(type (integer 0 #.most-positive-fixnum) index))
(sys:sap-ref-8 (buffer-sap buffer) index))
(defun (setf bref) (octet buffer index)
(declare (type (unsigned-byte 8) octet)
(type simple-stream-buffer buffer)
(type (integer 0 #.most-positive-fixnum) index))
(setf (sys:sap-ref-8 (buffer-sap buffer) index) octet))
(defun buffer-copy (src soff dst doff length)
(declare (type simple-stream-buffer src dst)
(type fixnum soff doff length))
(sys:without-gcing ;; is this necessary??
(kernel:system-area-copy (buffer-sap src) (* soff 8)
(buffer-sap dst) (* doff 8)
(* length 8))))
#-(or big-endian little-endian)
(eval-when (:compile-toplevel)
(push (c::backend-byte-order c::*target-backend*) *features*))
(defun vector-elt-width (vector)
;; Return octet-width of vector elements
(etypecase vector
;; (simple-array fixnum (*)) not supported
;; (simple-array base-char (*)) treated specially; don't call this
((simple-array bit (*)) 1/8)
((simple-array (unsigned-byte 2) (*)) 1/4)
((simple-array (unsigned-byte 4) (*)) 1/2)
((simple-array (signed-byte 8) (*)) 1)
((simple-array (unsigned-byte 8) (*)) 1)
((simple-array (signed-byte 16) (*)) 2)
((simple-array (unsigned-byte 16) (*)) 2)
((simple-array (signed-byte 32) (*)) 4)
((simple-array (unsigned-byte 32) (*)) 4)
((simple-array single-float (*)) 4)
((simple-array double-float (*)) 8)
((simple-array (complex single-float) (*)) 8)
((simple-array (complex double-float) (*)) 16)
#+long-float
((simple-array long-float (*)) 10)
#+long-float
((simple-array (complex long-float) (*)) 20)
#+double-double
((simple-array double-double-float (*)) 16)
#+double-double
((simple-array (complex double-double-float) (*)) 32)))
(defun endian-swap-value (vector endian-swap)
(case endian-swap
(:network-order
#+big-endian 0
;; This is needed because the little-endian (x86) architectures
;; store the lowest indexed element in the least significant part
;; of a byte. On a big-endian machine (sparc, ppc), the lowest
;; indexed element is at the most significant part of a byte.
#+little-endian
(typecase vector
((array (unsigned-byte 4) (*))
-1)
((array (unsigned-byte 2) (*))
-2)
((array (unsigned-byte 1) (*))
-8)
(t
(1- (vector-elt-width vector)))))
(:byte-8 0)
(:byte-16 1)
(:byte-32 3)
(:byte-64 7)
(:byte-128 15)
;; additions by Lynn Quam
(:machine-endian 0)
(:big-endian
#+big-endian 0
#+little-endian
(typecase vector
((array (unsigned-byte 4) (*))
-1)
((array (unsigned-byte 2) (*))
-2)
((array (unsigned-byte 1) (*))
-8)
(t
(1- (vector-elt-width vector)))))
(:little-endian
#+big-endian
(typecase vector
((array (unsigned-byte 4) (*))
-1)
((array (unsigned-byte 2) (*))
-2)
((array (unsigned-byte 1) (*))
-8)
(t
(1- (vector-elt-width vector))))
#+little-endian 0)
(otherwise endian-swap)))
;;;; Superclass defined by the ANSI Spec
(defstruct (file-stream
(:include lisp-stream)
(:constructor nil)
(:copier nil)))
(defstruct (fd-stream
(:print-function %print-fd-stream)
(:constructor %make-fd-stream)
(misc #'fd-stream-misc-routine)))
(name nil) ; The name of this stream
(file nil) ; The file this stream is for
;;
;; The backup file namestring for the old file, for :if-exists :rename or
;; :rename-and-delete.
(original nil :type (or simple-string null))
;;
;;; Number of bytes per element.
(element-size 1 :type index)
(element-type 'base-char) ; The type of element being transfered.
;;
;; Controls when the output buffer is flushed.
(buffering :full :type (member :full :line :none))
;;
;; Character position if known.
(char-pos nil :type (or index null))
;;
;; T if input is waiting on FD. :EOF if we hit EOF.
(listen nil :type (member nil t :eof))
;;
(ibuf-sap nil :type (or system-area-pointer null))
(ibuf-length nil :type (or index null))
(ibuf-head 0 :type index)
(ibuf-tail 0 :type index)
(obuf-sap nil :type (or system-area-pointer null))
(obuf-length nil :type (or index null))
(obuf-tail 0 :type index)
;; Output flushed, but not written due to non-blocking io.
(output-later nil)
(handler nil)
;;
;; Timeout specified for this stream, or NIL if none.
(timeout nil :type (or index null))
;;
;; Pathname of the file this stream is opened to (returned by PATHNAME.)
(pathname nil :type (or pathname null))
;;
;; External format support
;;
;; @@ I want to use :default here, but keyword pkg isn't set up yet at boot
;; so initialize to NIL and fix it in SET-ROUTINES
#+unicode
(external-format nil :type (or null keyword cons))
;;
;; State for octets-to-char (for reading from a stream). The
;; contents of the state can be anything and is defined by the
;; external format.
;;
;; State for char-to-octets (for writing to a stream). The contents
;; of the state can be anything and is defined by the external
;; format. If not NIL, then the CAR is used by char-to-octets to
;; hold some state information, and the CDR is available to the
;; external format to hold whatever state information is needed.
#+unicode
(co-state nil)
#+unicode
(last-char-read-size 0 :type index)
;;
;; The number of octets in in-buffer. Normally equal to
;; in-buffer-length, but could be less if we reached the
;; end-of-file.
#+unicode
;;
;; Indicates how to handle errors when converting octets to
;; characters. If NIL, then the external format should handle it
;; itself, doing whatever is deemed appropriate. If non-NIL, this
;; should be a function (or symbol) that the external format can
;; funcall to deal with the error. The function should take three
;; arguments: a message string, the offending octet, and the number
;; of octets read so far in decoding; if the function returns it
;; should return the codepoint of the desired replacement character.
;;
;; Like OCTETS-TO-CHAR-ERROR, but for converting characters to
;; octets for output. The function takes two arguments: a message
;; string and the codepoint that cannot be converted. The function
;; should return the octet that should be output.
(declare (ignore depth) (stream stream))
(format stream "#<Stream for ~A>"
(fd-stream-name fd-stream)))
;; CMUCL extension. This is a FD-STREAM, but it allows reading and
;; writing of 8-bit characters and unsigned bytes from the stream.
(defstruct (binary-text-stream
(:print-function %print-binary-text-stream)
(:constructor %make-binary-text-stream)
(:include fd-stream)))
(defun %print-binary-text-stream (fd-stream stream depth)
(declare (ignore depth) (stream stream))
(format stream "#<Binary-text Stream for ~A>"
(fd-stream-name fd-stream)))
(define-condition io-timeout (stream-error)
((direction :reader io-timeout-direction :initarg :direction))
(:report
(lambda (condition stream)
(format stream (intl:gettext "Timeout ~(~A~)ing ~S.")
(io-timeout-direction condition)
(stream-error-stream condition)))))
;;;; Output routines and related noise.
(defvar *output-routines* ()
"List of all available output routines. Each element is a list of the
element-type output, the kind of buffering, the function name, and the number
of bytes per element.")
;;; DO-OUTPUT-LATER -- internal
;;;
;;; Called by the server when we can write to the given file descriptor.
;;; Attempt to write the data again. If it worked, remove the data from the
;;; output-later list. If it didn't work, something is wrong.
;;;
(defun do-output-later (stream)
(let* ((stuff (pop (fd-stream-output-later stream)))
(base (car stuff))
(start (cadr stuff))
(end (caddr stuff))
(declare (type index start end length))
(error (intl:gettext "Write would have blocked, but SERVER told us to go."))
(error (intl:gettext "While writing ~S: ~A")
((eql count length) ; Hot damn, it worked.
(when reuse-sap
(push base *available-buffers*)))
(fd-stream-output-later stream))))))
(unless (fd-stream-output-later stream)
(system:remove-fd-handler (fd-stream-handler stream))
(setf (fd-stream-handler stream) nil)))
;;; OUTPUT-LATER -- internal
;;;
;;; Arrange to output the string when we can write on the file descriptor.
(defun output-later (stream base start end reuse-sap)
(cond ((null (fd-stream-output-later stream))
(setf (fd-stream-output-later stream)
(list (list base start end reuse-sap)))
(setf (fd-stream-handler stream)
(system:add-fd-handler (fd-stream-fd stream)
:output
#'(lambda (fd)
(declare (ignore fd))
(do-output-later stream)))))
(t
(nconc (fd-stream-output-later stream)
(list (list base start end reuse-sap)))))
(when reuse-sap
(setf (fd-stream-obuf-sap stream) new-buffer)
(setf (fd-stream-obuf-length stream) bytes-per-buffer))))
;;; DO-OUTPUT -- internal
;;;
;;; Output the given noise. Check to see if there are any pending writes. If
;;; so, just queue this one. Otherwise, try to write it. If this would block,
;;; queue it.
;;;
(defun do-output (stream base start end reuse-sap)
(declare (type fd-stream stream)
(type (or system-area-pointer (simple-array * (*))) base)
(type index start end))
(if (not (null (fd-stream-output-later stream))) ; something buffered.
(progn
(output-later stream base start end reuse-sap)
;; ### check to see if any of this noise can be output
)
(let ((length (- end start)))
(multiple-value-bind
(count errno)
(unix:unix-write (fd-stream-fd stream) base start length)
(output-later stream base start end reuse-sap)
(error 'simple-stream-error
:stream stream
:format-control "while writing: ~A"
:format-arguments (list (unix:get-unix-error-msg errno)))))
(output-later stream base (the index (+ start count))
end reuse-sap)))))))
#+unicode
(stream::def-ef-macro ef-flush (extfmt lisp stream::+ef-max+ stream::+ef-flush+)
`(lambda (stream)
(declare (type fd-stream stream))
(let* ((tail (fd-stream-obuf-tail stream)))
(declare (type index tail))
(cond
((stream::ef-flush-state ,(stream::find-external-format extfmt))
(len (fd-stream-obuf-length stream)))
(declare (type sys:system-area-pointer sap)
(type index len)
(ignorable sap len))
(stream::flush-state ,extfmt
(fd-stream-co-state stream)
(lambda (byte)
(when (= tail len)
(do-output stream sap 0 tail t)
(setq sap (fd-stream-obuf-sap stream)
tail 0))
(setf (bref sap (1- (incf tail))) byte))
(fd-stream-char-to-octets-error stream))
(setf (fd-stream-obuf-tail stream) tail)))
(t
;; No flush-state function, so just output a replacement
;; character (or signal an error). We hack the co-state to
;; what we need for this to work. This should be ok because
;; we're closing the file anyway.
(let* ((state (fd-stream-co-state stream))
(c (car state)))
(when (and state c)
(setf (fd-stream-co-state stream)
(cons nil (cdr state)))
(funcall (ef-cout (fd-stream-external-format stream))
stream
;; Handle bare surrogates or use the
;; replacement character.
(if (lisp::surrogatep c)
(if (fd-stream-char-to-octets-error stream)
(funcall (fd-stream-char-to-octets-error stream)
"Flushing bare surrogate #x~4,0X is illegal"
(char-code c))
(code-char stream:+replacement-character-code+))
c))))))
(values))))
;;; FLUSH-OUTPUT-BUFFER -- internal
;;;
;;; Flush any data in the output buffer.
;;;
(defun flush-output-buffer (stream)
(let ((length (fd-stream-obuf-tail stream)))
(unless (= length 0)
(do-output stream (fd-stream-obuf-sap stream) 0 length t)
(setf (fd-stream-obuf-tail stream) 0))))
;;; DEF-OUTPUT-ROUTINES -- internal
;;;
;;; Define output routines that output numbers size bytes long for the
;;; given bufferings. Use body to do the actual output.
;;;
(defmacro def-output-routines ((name size &rest bufferings) &body body)
(cons 'progn
(mapcar
#'(lambda (buffering)
(let ((function
(intern (let ((*print-case* :upcase))
(format nil name (car buffering))))))
`(progn
(defun ,function (stream byte)
,(unless (eq (car buffering) :none)
`(when (< (fd-stream-obuf-length stream)
(+ (fd-stream-obuf-tail stream)
,size))
(flush-output-buffer stream)))
;;
;; If there is any input read from UNIX but not
;; supplied to the user of the stream, reposition
;; to the real file position as seen from Lisp.
,(unless (eq (car buffering) :none)
`(when (> (fd-stream-ibuf-tail stream)
(fd-stream-ibuf-head stream))
(file-position stream (file-position stream))))
,@body
(incf (fd-stream-obuf-tail stream) ,size)
,(ecase (car buffering)
(:none
`(flush-output-buffer stream))
(:line
`(when (eql (char-code byte) (char-code #\Newline))
(flush-output-buffer stream)))
(:full
))
(values))
(setf *output-routines*
(nconc *output-routines*
',(mapcar
#'(lambda (type)
(list type
(car buffering)
function
size))
(cdr buffering)))))))
bufferings)))
(def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
1
(:none character)
(:line character)
(:full character))
(if (char= byte #\Newline)
(setf (fd-stream-char-pos stream) 0)
(incf (fd-stream-char-pos stream)))
(setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
(char-code byte)))
#+unicode
(def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
1
(:none character)
(:line character)
(:full character))
(if (char= byte #\Newline)
(setf (fd-stream-char-pos stream) 0)
(incf (fd-stream-char-pos stream)))
;; FIXME! We only use the low 8 bits of a character!
(setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
(logand #xff (char-code byte))))
(def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
(:none (unsigned-byte 8))
(:full (unsigned-byte 8)))
(setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
byte))
(def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
1
(:none (signed-byte 8))
(:full (signed-byte 8)))
(setf (signed-sap-ref-8 (fd-stream-obuf-sap stream)
(fd-stream-obuf-tail stream))
byte))
(def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
(:none (unsigned-byte 16))
(:full (unsigned-byte 16)))
(setf (sap-ref-16 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
(def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
2
(:none (signed-byte 16))
(:full (signed-byte 16)))
(setf (signed-sap-ref-16 (fd-stream-obuf-sap stream)
(fd-stream-obuf-tail stream))
byte))
(def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
(:none (unsigned-byte 32))
(:full (unsigned-byte 32)))
(setf (sap-ref-32 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
(def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
4
(:none (signed-byte 32))
(:full (signed-byte 32)))
(setf (signed-sap-ref-32 (fd-stream-obuf-sap stream)
(fd-stream-obuf-tail stream))
byte))
(stream::def-ef-macro ef-cout (extfmt lisp stream::+ef-max+ stream::+ef-cout+)
`(lambda (stream char)
(declare (type fd-stream stream)
(type character char)
(optimize (speed 3) (space 0) (debug 0) (safety 0)))
;; If there is any input read from UNIX but not
;; supplied to the user of the stream, reposition
;; to the real file position as seen from Lisp.
(when (> (fd-stream-ibuf-tail stream)
(fd-stream-ibuf-head stream))
(file-position stream (file-position stream)))
(let* ((sap (fd-stream-obuf-sap stream))
(len (fd-stream-obuf-length stream))
(tail (fd-stream-obuf-tail stream)))
(declare (type sys:system-area-pointer sap) (type index len tail))
(stream::char-to-octets ,extfmt
char
(fd-stream-co-state stream)
(lambda (byte)
(when (= tail len)
(do-output stream sap 0 tail t)
(setq sap (fd-stream-obuf-sap stream)
tail 0))
(fd-stream-char-to-octets-error stream))
(setf (fd-stream-obuf-tail stream) tail))
(if (char= char #\Newline)
(setf (fd-stream-char-pos stream) 0)
(incf (fd-stream-char-pos stream)))
(ecase (fd-stream-buffering stream)
(:none (flush-output-buffer stream))
(:line (when (char= char #\Newline) (flush-output-buffer stream)))
(:full #| do nothing |#))
(values)))
;;; OUTPUT-RAW-BYTES -- public
;;;
;;; Does the actual output. If there is space to buffer the string, buffer
;;; it. If the string would normally fit in the buffer, but doesn't because
;;; of other stuff in the buffer, flush the old noise out of the buffer and
;;; put the string in it. Otherwise we have a very long string, so just
;;; send it directly (after flushing the buffer, of course).
;;;
(defun output-raw-bytes (stream thing &optional start end)
"Output THING to stream. THING can be any kind of vector or a sap. If THING
is a SAP, END must be supplied (as length won't work)."
(let ((start (or start 0))
(end (or end (length (the (simple-array * (*)) thing)))))
(declare (type index start end))
;;
;; If there is any input read from UNIX but not
;; supplied to the user of the stream, reposition
;; to the real file position as seen from Lisp.
(when (> (fd-stream-ibuf-tail stream)
(fd-stream-ibuf-head stream))
(file-position stream (file-position stream)))
(let* ((len (fd-stream-obuf-length stream))
(tail (fd-stream-obuf-tail stream))
(space (- len tail))
(bytes (- end start))
(newtail (+ tail bytes)))
(cond ((minusp bytes) ; Error case
(cerror (intl:gettext "Just go on as if nothing happened...")
(intl:gettext "~S called with :END before :START!")
'output-raw-bytes))
((zerop bytes)) ; Easy case
((<= bytes space)
(if (system-area-pointer-p thing)
(system-area-copy thing
(* start vm:byte-bits)
(fd-stream-obuf-sap stream)
(* tail vm:byte-bits)
(* bytes vm:byte-bits))
(copy-to-system-area thing
(+ (* start vm:byte-bits)
(* vm:vector-data-offset vm:word-bits))
(fd-stream-obuf-sap stream)
(* tail vm:byte-bits)
(* bytes vm:byte-bits)))
(setf (fd-stream-obuf-tail stream) newtail))
((<= bytes len)
(flush-output-buffer stream)
(if (system-area-pointer-p thing)
(system-area-copy thing
(* start vm:byte-bits)
(fd-stream-obuf-sap stream)
0
(* bytes vm:byte-bits))
(copy-to-system-area thing
(+ (* start vm:byte-bits)
(* vm:vector-data-offset vm:word-bits))
(fd-stream-obuf-sap stream)
0
(* bytes vm:byte-bits)))
(setf (fd-stream-obuf-tail stream) bytes))
(t
(flush-output-buffer stream)
(do-output stream thing start end nil))))))
;;; FD-SOUT -- internal
;;;
;;; Routine to use to output a string. If the stream is unbuffered, slam
;;; the string down the file descriptor, otherwise use OUTPUT-RAW-BYTES to
;;; buffer the string. Update charpos by checking to see where the last newline
;;; was.
;;;
;;; Note: some bozos (the FASL dumper) call write-string with things other
;;; than strings. Therefore, we must make sure we have a string before calling
;;; position on it.
;;;
(stream::def-ef-macro ef-sout (extfmt lisp stream::+ef-max+ stream::+ef-sout+)
`(lambda (stream string start end)
(declare (type fd-stream stream)
(type simple-string string)
(type index start end)
(optimize (speed 3) (space 0) (safety 0) (debug 0)))
;; If there is any input read from UNIX but not
;; supplied to the user of the stream, reposition
;; to the real file position as seen from Lisp.
;; (maybe the caller should do this?)
(when (> (fd-stream-ibuf-tail stream)
(fd-stream-ibuf-head stream))
(file-position stream (file-position stream)))
(let* ((sap (fd-stream-obuf-sap stream))
(len (fd-stream-obuf-length stream))
(tail (fd-stream-obuf-tail stream)))
(declare (type sys:system-area-pointer sap) (type index len tail))
(dotimes (i (- end start))
(stream::char-to-octets ,extfmt
(schar string (+ i start))
(fd-stream-co-state stream)
(lambda (byte)
(when (= tail len)
(do-output stream sap 0 tail t)
(setq sap (fd-stream-obuf-sap stream)
tail 0))
(fd-stream-char-to-octets-error stream)))
(setf (fd-stream-obuf-tail stream) tail))))
#-unicode
(defun fd-sout (stream thing start end)
(let ((start (or start 0))
(end (or end (length (the vector thing)))))
(declare (type index start end))
(let ((last-newline (and (find #\newline (the simple-string thing)
:start start :end end)
(position #\newline (the simple-string thing)
:from-end t
:start start
:end end))))
(ecase (fd-stream-buffering stream)
(:full
(output-raw-bytes stream thing start end))
(:line
(output-raw-bytes stream thing start end)
(when last-newline
(flush-output-buffer stream)))
(:none
(do-output stream thing start end nil)))
(if last-newline
(setf (fd-stream-char-pos stream)
(- end last-newline 1))
(incf (fd-stream-char-pos stream)
(- end start))))
(do-output stream thing start end nil))))))
;; Temporary. The final version is defined in fd-stream-extfmt.lisp
(defun fd-sout (stream thing start end)
(declare (type string thing))
(let ((start (or start 0))
(end (or end (length (the vector thing)))))
(declare (type index start end))
(cond
((stringp thing) ; FIXME - remove this test
(let ((out (fd-stream-out stream)))
(do ((index start (+ index 1)))
((>= index end))
(funcall out stream (elt thing index))))))))
(defmacro output-wrapper ((stream size buffering) &body body)
(let ((stream-var (gensym)))
`(let ((,stream-var ,stream))
,(unless (eq (car buffering) :none)
`(when (< (fd-stream-obuf-length ,stream-var)
(+ (fd-stream-obuf-tail ,stream-var)
,size))
(flush-output-buffer ,stream-var)))
,(unless (eq (car buffering) :none)
`(when (> (fd-stream-ibuf-tail ,stream-var)
(fd-stream-ibuf-head ,stream-var))
(file-position ,stream-var (file-position ,stream-var))))
,@body
(incf (fd-stream-obuf-tail ,stream-var) ,size)
,(ecase (car buffering)
(:none
`(flush-output-buffer ,stream-var))
(:line
`(when (eq (char-code byte) (char-code #\Newline))
(flush-output-buffer ,stream-var)))
(:full))
(values))))
;;; PICK-OUTPUT-ROUTINE -- internal
;;;
;;; Find an output routine to use given the type and buffering. Return as
;;; multiple values the routine, the real type transfered, and the number of
;;; bytes per element.
;;;
(defun pick-output-routine (type buffering)
(dolist (entry *output-routines*)
(when (and (subtypep type (car entry))
(eq buffering (cadr entry)))
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
(return-from pick-output-routine
(values (symbol-function (caddr entry))
(car entry)
(cadddr entry)))))
;; KLUDGE: also see comments in PICK-INPUT-ROUTINE
(loop for i from 40 by 8 to max-stream-element-size ; ARB (KLUDGE)
if (subtypep type `(unsigned-byte ,i))
do (return-from pick-output-routine
(values
(ecase buffering
(:none
(lambda (stream byte)
(output-wrapper (stream (/ i 8) (:none))
(loop for j from 0 below (/ i 8)
do (setf (sap-ref-8
(fd-stream-obuf-sap stream)
(+ j (fd-stream-obuf-tail stream)))
(ldb (byte 8 (- i 8 (* j 8))) byte))))))
(:full
(lambda (stream byte)
(output-wrapper (stream (/ i 8) (:full))
(loop for j from 0 below (/ i 8)
do (setf (sap-ref-8
(fd-stream-obuf-sap stream)
(+ j (fd-stream-obuf-tail stream)))
(ldb (byte 8 (- i 8 (* j 8))) byte)))))))
`(unsigned-byte ,i)
(/ i 8))))
(loop for i from 40 by 8 to max-stream-element-size ; ARB (KLUDGE)
if (subtypep type `(signed-byte ,i))
do (return-from pick-output-routine
(values
(ecase buffering
(:none
(lambda (stream byte)
(output-wrapper (stream (/ i 8) (:none))
(loop for j from 0 below (/ i 8)
do (setf (sap-ref-8
(fd-stream-obuf-sap stream)
(+ j (fd-stream-obuf-tail stream)))
(ldb (byte 8 (- i 8 (* j 8))) byte))))))
(:full
(lambda (stream byte)
(output-wrapper (stream (/ i 8) (:full))
(loop for j from 0 below (/ i 8)
do (setf (sap-ref-8
(fd-stream-obuf-sap stream)
(+ j (fd-stream-obuf-tail stream)))
(ldb (byte 8 (- i 8 (* j 8))) byte)))))))
`(signed-byte ,i)
(/ i 8)))))
;;;; Input routines and related noise.
(defvar *input-routines* ()
"List of all available input routines. Each element is a list of the
element-type input, the function name, and the number of bytes per element.")
;;; DO-INPUT -- internal
;;;
;;; Fills the input buffer, and returns the first character. Throws to
;;; eof-input-catcher if the eof was reached. Drops into system:server if
;;; necessary.
;;;
(defun do-input (stream)
(let ((fd (fd-stream-fd stream))
(ibuf-sap (fd-stream-ibuf-sap stream))
(buflen (fd-stream-ibuf-length stream))
(head (fd-stream-ibuf-head stream))
(lcrs #-unicode 0
#+unicode (fd-stream-last-char-read-size stream))
(setf head lcrs)
(setf tail lcrs)
(setf (fd-stream-ibuf-head stream) lcrs)
(setf (fd-stream-ibuf-tail stream) lcrs))
(decf tail (- head lcrs))
(system-area-copy ibuf-sap (* (- head lcrs) vm:byte-bits)
ibuf-sap 0 (* tail vm:byte-bits))
(setf head lcrs)
(setf (fd-stream-ibuf-head stream) lcrs)
(setf (fd-stream-ibuf-tail stream) tail))))
(setf (fd-stream-listen stream) nil)
(multiple-value-bind
(count errno)
(alien:with-alien ((read-fds (alien:struct unix:fd-set)))
(unix:fd-zero read-fds)
(unix:fd-set fd read-fds)
(unix:unix-fast-select (1+ fd) (alien:addr read-fds) nil nil 0 0))
;; Wait if input is not available or if interrupted.
(when (or (eql count 0)
(and (not count) (eql errno unix:eintr)))
(unless #-mp (system:wait-until-fd-usable
fd :input (fd-stream-timeout stream))
#+mp (mp:process-wait-until-fd-usable
fd :input (fd-stream-timeout stream))
(error 'io-timeout :stream stream :direction :read))))
(system:int-sap (+ (system:sap-int ibuf-sap) tail))
(- buflen tail))
(cond ((null count)
;; What kinds of errors do we want to look at and what do
;; we want them to do?
(cond ((eql errno unix:ewouldblock)
(unless #-mp (system:wait-until-fd-usable
fd :input (fd-stream-timeout stream))
#+mp (mp:process-wait-until-fd-usable
fd :input (fd-stream-timeout stream))
(error 'io-timeout :stream stream :direction :read))
(do-input stream))
((eql errno unix:econnreset)
(error 'socket-error
:format-control "Socket connection reset: ~A"
:format-arguments (list (unix:get-unix-error-msg errno))
:errno errno))
(t
(error (intl:gettext "Error reading ~S: ~A")
stream
(unix:get-unix-error-msg errno)))))
(setf (fd-stream-listen stream) :eof)
(throw 'eof-input-catcher nil))
(t
(incf (fd-stream-ibuf-tail stream) count))))))
;;; INPUT-AT-LEAST -- internal
;;;
;;; Makes sure there are at least ``bytes'' number of bytes in the input
;;; buffer. Keeps calling do-input until that condition is met.
;;;
(defmacro input-at-least (stream bytes)
(let ((stream-var (gensym))
(bytes-var (gensym)))
`(let ((,stream-var ,stream)
(,bytes-var ,bytes))
(loop
(when (>= (- (fd-stream-ibuf-tail ,stream-var)
(fd-stream-ibuf-head ,stream-var))
,bytes-var)
(return))
(do-input ,stream-var)))))
;;; Macro to wrap around all input routines to handle eof-error noise.
(defmacro input-wrapper ((stream bytes eof-error eof-value &optional type) &body read-forms)
(let ((stream-var (gensym))
(element-var (gensym)))
`(let ((,stream-var ,stream))
,(if (eq type 'character)
`(fd-stream-unread ,stream-var)
`(char-code (fd-stream-unread ,stream-var)))
(setf (fd-stream-unread ,stream-var) nil)
(setf (fd-stream-listen ,stream-var) nil))
(let ((,element-var
(catch 'eof-input-catcher
(input-at-least ,stream-var ,bytes)
,@read-forms)))
(cond (,element-var
(incf (fd-stream-ibuf-head ,stream-var) ,bytes)
,element-var)
(t
(eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
;;; DEF-INPUT-ROUTINE -- internal
;;;
;;; Defines an input routine.
;;;
(defmacro def-input-routine (name
(type size sap head)
&rest body)
`(progn
(defun ,name (stream eof-error eof-value)
(input-wrapper (stream ,size eof-error eof-value ,type)
(let ((,sap (fd-stream-ibuf-sap stream))
(,head (fd-stream-ibuf-head stream)))
,@body)))
(setf *input-routines*
(nconc *input-routines*
(list (list ',type ',name ',size))))))
;;; INPUT-CHARACTER -- internal
;;;
;;; Routine to use in stream-in slot for reading string chars.
;;;
(def-input-routine input-character
(character 1 sap head)
(code-char (sap-ref-8 sap head)))