0.9.13.10: better SB-BSD-SOCKETS on Windows
[sbcl.git] / contrib / sb-bsd-sockets / sockets.lisp
1 (in-package "SB-BSD-SOCKETS")
2
3 ;;;; Methods, classes, functions for sockets.  Protocol-specific stuff
4 ;;;; is deferred to inet.lisp, unix.lisp, etc
5
6 (eval-when (:load-toplevel :compile-toplevel :execute)
7
8 (defclass socket ()
9   ((file-descriptor :initarg :descriptor
10                     :reader socket-file-descriptor)
11    (family :initform (error "No socket family")
12            :reader socket-family)
13    (protocol :initarg :protocol
14              :reader socket-protocol
15              :documentation "Protocol used by the socket. If a
16 keyword, the symbol-name of the keyword will be passed to
17 GET-PROTOCOL-BY-NAME downcased, and the returned value used as
18 protocol. Other values are used as-is.")
19    (type  :initarg :type
20           :reader socket-type
21           :documentation "Type of the socket: :STREAM or :DATAGRAM.")
22    (stream))
23   (:documentation "Common base class of all sockets, not ment to be
24 directly instantiated.")))
25
26 (defmethod print-object ((object socket) stream)
27   (print-unreadable-object (object stream :type t :identity t)
28                            (princ "descriptor " stream)
29                            (princ (slot-value object 'file-descriptor) stream)))
30
31
32 (defmethod shared-initialize :after ((socket socket) slot-names
33                                      &key protocol type
34                                      &allow-other-keys)
35   (let* ((proto-num
36           (cond ((and protocol (keywordp protocol))
37                  (get-protocol-by-name (string-downcase (symbol-name protocol))))
38                 (protocol protocol)
39                 (t 0)))
40          (fd (or (and (slot-boundp socket 'file-descriptor)
41                       (socket-file-descriptor socket))
42                  (sockint::socket (socket-family socket)
43                                   (ecase type
44                                     ((:datagram) sockint::sock-dgram)
45                                     ((:stream) sockint::sock-stream))
46                                   proto-num))))
47       (if (= fd -1) (socket-error "socket"))
48       (setf (slot-value socket 'file-descriptor) fd
49             (slot-value socket 'protocol) proto-num
50             (slot-value socket 'type) type)
51       (sb-ext:finalize socket (lambda () (sockint::close fd)))))
52
53 \f
54
55 (defgeneric make-sockaddr-for (socket &optional sockaddr &rest address)
56   (:documentation "Return a Socket Address object suitable for use with SOCKET.
57 When SOCKADDR is passed, it is used instead of a new object."))
58
59 (defgeneric free-sockaddr-for (socket sockaddr)
60   (:documentation "Deallocate a Socket Address object that was
61 created for SOCKET."))
62
63 (defmacro with-sockaddr-for ((socket sockaddr &optional sockaddr-args) &body body)
64   `(let ((,sockaddr (apply #'make-sockaddr-for ,socket nil ,sockaddr-args)))
65      (unwind-protect (progn ,@body)
66        (free-sockaddr-for ,socket ,sockaddr))))
67
68 ;; we deliberately redesign the "bind" interface: instead of passing a
69 ;; sockaddr_something as second arg, we pass the elements of one as
70 ;; multiple arguments.
71
72 (defgeneric socket-bind (socket &rest address)
73   (:documentation "Bind SOCKET to ADDRESS, which may vary according to
74 socket family.  For the INET family, pass ADDRESS and PORT as two
75 arguments; for FILE address family sockets, pass the filename string.
76 See also bind(2)"))
77
78 (defmethod socket-bind ((socket socket)
79                         &rest address)
80   (with-sockaddr-for (socket sockaddr address)
81     (if (= (sockint::bind (socket-file-descriptor socket)
82                           sockaddr
83                           (size-of-sockaddr socket))
84            -1)
85         (socket-error "bind"))))
86
87 \f
88 (defgeneric socket-accept (socket)
89   (:documentation "Perform the accept(2) call, returning a
90 newly-created connected socket and the peer address as multiple
91 values"))
92
93 (defmethod socket-accept ((socket socket))
94   (with-sockaddr-for (socket sockaddr)
95     (let ((fd (sockint::accept (socket-file-descriptor socket)
96                                sockaddr
97                                (size-of-sockaddr socket))))
98       (cond
99         ((and (= fd -1) (= sockint::EAGAIN (sb-unix::get-errno)))
100          nil)
101         ((= fd -1) (socket-error "accept"))
102         (t (apply #'values
103                   (let ((s (make-instance (class-of socket)
104                               :type (socket-type socket)
105                               :protocol (socket-protocol socket)
106                               :descriptor fd)))
107                     (sb-ext:finalize s (lambda () (sockint::close fd))))
108                   (multiple-value-list (bits-of-sockaddr socket sockaddr))))))))
109
110 (defgeneric socket-connect (socket &rest address)
111   (:documentation "Perform the connect(2) call to connect SOCKET to a
112   remote PEER.  No useful return value."))
113
114 (defmethod socket-connect ((socket socket) &rest peer)
115   (with-sockaddr-for (socket sockaddr peer)
116     (if (= (sockint::connect (socket-file-descriptor socket)
117                              sockaddr
118                              (size-of-sockaddr socket))
119            -1)
120         (socket-error "connect"))))
121
122 (defgeneric socket-peername (socket)
123   (:documentation "Return the socket's peer; depending on the address
124   family this may return multiple values"))
125
126 (defmethod socket-peername ((socket socket))
127   (with-sockaddr-for (socket sockaddr)
128     (when (= (sockint::getpeername (socket-file-descriptor socket)
129                                     sockaddr
130                                     (size-of-sockaddr socket))
131              -1)
132       (socket-error "getpeername"))
133     (bits-of-sockaddr socket sockaddr)))
134
135 (defgeneric socket-name (socket)
136   (:documentation "Return the address (as vector of bytes) and port
137   that the socket is bound to, as multiple values."))
138
139 (defmethod socket-name ((socket socket))
140   (with-sockaddr-for (socket sockaddr)
141     (when (= (sockint::getsockname (socket-file-descriptor socket)
142                                    sockaddr
143                                    (size-of-sockaddr socket))
144              -1)
145       (socket-error "getsockname"))
146     (bits-of-sockaddr socket sockaddr)))
147
148
149 ;;; There are a whole bunch of interesting things you can do with a
150 ;;; socket that don't really map onto "do stream io", especially in
151 ;;; CL which has no portable concept of a "short read".  socket-receive
152 ;;; allows us to read from an unconnected socket into a buffer, and
153 ;;; to learn who the sender of the packet was
154
155 (defgeneric socket-receive (socket buffer length
156                             &key
157                             oob peek waitall element-type)
158   (:documentation "Read LENGTH octets from SOCKET into BUFFER (or a freshly-consed buffer if
159 NIL), using recvfrom(2).  If LENGTH is NIL, the length of BUFFER is
160 used, so at least one of these two arguments must be non-NIL.  If
161 BUFFER is supplied, it had better be of an element type one octet wide.
162 Returns the buffer, its length, and the address of the peer
163 that sent it, as multiple values.  On datagram sockets, sets MSG_TRUNC
164 so that the actual packet length is returned even if the buffer was too
165 small"))
166
167 (defmethod socket-receive ((socket socket) buffer length
168                            &key
169                            oob peek waitall
170                            (element-type 'character))
171   (with-sockaddr-for (socket sockaddr)
172     (let ((flags
173            (logior (if oob sockint::MSG-OOB 0)
174                    (if peek sockint::MSG-PEEK 0)
175                    (if waitall sockint::MSG-WAITALL 0)
176                    #+linux sockint::MSG-NOSIGNAL ;don't send us SIGPIPE
177                    (if (eql (socket-type socket) :datagram)
178                        sockint::msg-TRUNC 0))))
179       (unless (or buffer length)
180         (error "Must supply at least one of BUFFER or LENGTH"))
181       (unless length
182         (setf length (length buffer)))
183       (when buffer (setf element-type (array-element-type buffer)))
184       (unless (or (subtypep element-type 'character)
185                   (subtypep element-type 'integer))
186         (error "Buffer element-type must be either a character or an integer subtype."))
187       (unless buffer
188         (setf buffer (make-array length :element-type element-type)))
189       ;; really big FIXME: This whole copy-buffer thing is broken.
190       ;; doesn't support characters more than 8 bits wide, or integer
191       ;; types that aren't (unsigned-byte 8).
192       (let ((copy-buffer (sb-alien:make-alien (array (sb-alien:unsigned 8) 1) length)))
193         (unwind-protect
194             (sb-alien:with-alien ((sa-len sockint::socklen-t (size-of-sockaddr socket)))
195               (let ((len
196                      (sockint::recvfrom (socket-file-descriptor socket)
197                                         copy-buffer
198                                         length
199                                         flags
200                                         sockaddr
201                                         (sb-alien:addr sa-len))))
202                 (cond
203                   ((and (= len -1) (= sockint::EAGAIN (sb-unix::get-errno))) nil)
204                   ((= len -1) (socket-error "recvfrom"))
205                   (t (loop for i from 0 below len
206                            do (setf (elt buffer i)
207                                     (cond
208                                       ((or (eql element-type 'character) (eql element-type 'base-char))
209                                        (code-char (sb-alien:deref (sb-alien:deref copy-buffer) i)))
210                                       (t (sb-alien:deref (sb-alien:deref copy-buffer) i)))))
211                      (apply #'values buffer len (multiple-value-list
212                                                  (bits-of-sockaddr socket sockaddr)))))))
213           (sb-alien:free-alien copy-buffer))))))
214
215 (defmacro with-vector-sap ((name vector) &body body)
216   `(sb-sys:with-pinned-objects (,vector)
217      (let ((,name (sb-sys:vector-sap ,vector)))
218        ,@body)))
219
220 (defgeneric socket-send (socket buffer length
221                                 &key
222                                 address
223                                 external-format
224                                 oob eor dontroute dontwait nosignal
225                                 #+linux confirm #+linux more)
226   (:documentation
227    "Send LENGTH octets from BUFFER into SOCKET, using sendto(2). If BUFFER
228 is a string, it will converted to octets according to EXTERNAL-FORMAT. If
229 LENGTH is NIL, the length of the octet buffer is used. The format of ADDRESS
230 depends on the socket type (for example for INET domain sockets it would
231 be a list of an IP address and a port). If no socket address is provided,
232 send(2) will be called instead. Returns the number of octets written."))
233
234 (defmethod socket-send ((socket socket) buffer length
235                         &key
236                         address
237                         (external-format :default)
238                         oob eor dontroute dontwait nosignal
239                         #+linux confirm #+linux more)
240   (let* ((flags
241           (logior (if oob sockint::MSG-OOB 0)
242                   (if eor sockint::MSG-EOR 0)
243                   (if dontroute sockint::MSG-DONTROUTE 0)
244                   (if dontwait sockint::MSG-DONTWAIT 0)
245                   (if nosignal sockint::MSG-NOSIGNAL 0)
246                   #+linux (if confirm sockint::MSG-CONFIRM 0)
247                   #+linux (if more sockint::MSG-MORE 0)))
248          (buffer (etypecase buffer
249                    (string
250                     (sb-ext:string-to-octets buffer
251                                              :external-format external-format
252                                              :null-terminate nil))
253                    ((simple-array (unsigned-byte 8))
254                     buffer)
255                    ((array (unsigned-byte 8))
256                     (make-array (length buffer)
257                                 :element-type '(unsigned-byte 8)
258                                 :initial-contents buffer))))
259          (len (with-vector-sap (buffer-sap buffer)
260                 (unless length
261                   (setf length (length buffer)))
262                 (if address
263                     (with-sockaddr-for (socket sockaddr address)
264                       (sb-alien:with-alien ((sa-len sockint::socklen-t
265                                                     (size-of-sockaddr socket)))
266                         (sockint::sendto (socket-file-descriptor socket)
267                                          buffer-sap
268                                          length
269                                          flags
270                                          sockaddr
271                                          sa-len)))
272                     (sockint::send (socket-file-descriptor socket)
273                                    buffer-sap
274                                    length
275                                    flags)))))
276     (cond
277       ((and (= len -1)
278             (member (sb-unix::get-errno)
279                     '(sockint::EAGAIN sockint::EINTR)))
280        nil)
281       ((= len -1)
282        (socket-error "sendto"))
283       (t len))))
284
285 (defgeneric socket-listen (socket backlog)
286   (:documentation "Mark SOCKET as willing to accept incoming connections.  BACKLOG
287 defines the maximum length that the queue of pending connections may
288 grow to before new connection attempts are refused.  See also listen(2)"))
289
290 (defmethod socket-listen ((socket socket) backlog)
291   (let ((r (sockint::listen (socket-file-descriptor socket) backlog)))
292     (if (= r -1)
293         (socket-error "listen"))))
294
295 (defgeneric socket-open-p (socket)
296   (:documentation "Return true if SOCKET is open; otherwise, return false.")
297   (:method ((socket t)) (error 'type-error
298                                :datum socket :expected-type 'socket)))
299
300 (defmethod socket-open-p ((socket socket))
301   (if (slot-boundp socket 'stream)
302       (open-stream-p (slot-value socket 'stream))
303       (/= -1 (socket-file-descriptor socket))))
304
305 (defgeneric socket-close (socket)
306   (:documentation "Close SOCKET.  May throw any kind of error that
307 write(2) would have thrown.  If SOCKET-MAKE-STREAM has been called,
308 calls CLOSE on that stream instead"))
309
310 (defmethod socket-close ((socket socket))
311   ;; the close(2) manual page has all kinds of warning about not
312   ;; checking the return value of close, on the grounds that an
313   ;; earlier write(2) might have returned successfully w/o actually
314   ;; writing the stuff to disk.  It then goes on to define the only
315   ;; possible error return as EBADF (fd isn't a valid open file
316   ;; descriptor).  Presumably this is an oversight and we could also
317   ;; get anything that write(2) would have given us.
318
319   ;; note that if you have a socket _and_ a stream on the same fd,
320   ;; the socket will avoid doing anything to close the fd in case
321   ;; the stream has done it already - if so, it may have been
322   ;; reassigned to some other file, and closing it would be bad
323
324   (let ((fd (socket-file-descriptor socket)))
325     (cond ((eql fd -1) ; already closed
326            nil)
327           ((slot-boundp socket 'stream)
328            (unwind-protect (close (slot-value socket 'stream)) ;; closes fd
329              (setf (slot-value socket 'file-descriptor) -1)
330              (slot-makunbound socket 'stream)))
331           (t
332            (sb-ext:cancel-finalization socket)
333            (handler-case
334                (if (= (sockint::close fd) -1)
335                    (socket-error "close"))
336              (bad-file-descriptor-error (c) (declare (ignore c)) nil)
337              (:no-error (c)
338                (declare (ignore c))
339                (setf (slot-value socket 'file-descriptor) -1)
340                nil))))))
341
342
343 (defgeneric socket-make-stream (socket &rest args)
344   (:documentation "Find or create a STREAM that can be used for IO on
345 SOCKET (which must be connected).  ARGS are passed onto
346 SB-SYS:MAKE-FD-STREAM."))
347
348 (defmethod socket-make-stream ((socket socket) &rest args)
349   (let ((stream
350          (and (slot-boundp socket 'stream) (slot-value socket 'stream))))
351     (unless stream
352       (setf stream (apply #'sb-sys:make-fd-stream
353                           (socket-file-descriptor socket)
354                           :name "a constant string"
355                           :dual-channel-p t
356                           args))
357       (setf (slot-value socket 'stream) stream)
358       (sb-ext:cancel-finalization socket))
359     stream))
360
361 \f
362
363 ;;; Error handling
364
365 (define-condition socket-error (error)
366   ((errno :initform nil
367           :initarg :errno
368           :reader socket-error-errno)
369    (symbol :initform nil :initarg :symbol :reader socket-error-symbol)
370    (syscall  :initform "outer space" :initarg :syscall :reader socket-error-syscall))
371   (:report (lambda (c s)
372              (let ((num (socket-error-errno c)))
373                (format s "Socket error in \"~A\": ~A (~A)"
374                        (socket-error-syscall c)
375                        (or (socket-error-symbol c) (socket-error-errno c))
376                        #+cmu (sb-unix:get-unix-error-msg num)
377                        #+sbcl (sb-int:strerror num)))))
378   (:documentation "Common base class of socket related conditions."))
379
380 ;;; watch out for slightly hacky symbol punning: we use both the value
381 ;;; and the symbol-name of sockint::efoo
382
383 (defmacro define-socket-condition (symbol name)
384   `(progn
385      (define-condition ,name (socket-error)
386        ((symbol :reader socket-error-symbol :initform (quote ,symbol))))
387      (export ',name)
388      (push (cons ,symbol (quote ,name)) *conditions-for-errno*)))
389
390 (defparameter *conditions-for-errno* nil)
391 ;;; this needs the rest of the list adding to it, really.  They also
392 ;;; need symbols to be added to constants.ccon
393 ;;; I haven't yet thought of a non-kludgey way of keeping all this in
394 ;;; the same place
395 (define-socket-condition sockint::EADDRINUSE address-in-use-error)
396 (define-socket-condition sockint::EAGAIN interrupted-error)
397 (define-socket-condition sockint::EBADF bad-file-descriptor-error)
398 (define-socket-condition sockint::ECONNREFUSED connection-refused-error)
399 (define-socket-condition sockint::ETIMEDOUT operation-timeout-error)
400 (define-socket-condition sockint::EINTR interrupted-error)
401 (define-socket-condition sockint::EINVAL invalid-argument-error)
402 (define-socket-condition sockint::ENOBUFS no-buffers-error)
403 (define-socket-condition sockint::ENOMEM out-of-memory-error)
404 (define-socket-condition sockint::EOPNOTSUPP operation-not-supported-error)
405 (define-socket-condition sockint::EPERM operation-not-permitted-error)
406 (define-socket-condition sockint::EPROTONOSUPPORT protocol-not-supported-error)
407 (define-socket-condition sockint::ESOCKTNOSUPPORT socket-type-not-supported-error)
408 (define-socket-condition sockint::ENETUNREACH network-unreachable-error)
409 (define-socket-condition sockint::ENOTCONN not-connected-error)
410
411 (defun condition-for-errno (err)
412   (or (cdr (assoc err *conditions-for-errno* :test #'eql)) 'socket-error))
413
414 #+cmu
415 (defun socket-error (where)
416   ;; Peter's debian/x86 cmucl packages (and sbcl, derived from them)
417   ;; use a direct syscall interface, and have to call UNIX-GET-ERRNO
418   ;; to update the value that unix-errno looks at.  On other CMUCL
419   ;; ports, (UNIX-GET-ERRNO) is not needed and doesn't exist
420   (when (fboundp 'unix::unix-get-errno) (unix::unix-get-errno))
421   (let ((condition (condition-for-errno sb-unix:unix-errno)))
422     (error condition :errno sb-unix:unix-errno  :syscall where)))
423
424 #+sbcl
425 (defun socket-error (where)
426   ;; FIXME: Our Texinfo documentation extracter need at least his to spit
427   ;; out the signature. Real documentation would be better...
428   ""
429   (let* ((errno  (sb-unix::get-errno))
430          (condition (condition-for-errno errno)))
431     (error condition :errno errno  :syscall where)))
432
433
434 (defgeneric bits-of-sockaddr (socket sockaddr)
435   (:documentation "Return protocol-dependent bits of parameter
436 SOCKADDR, e.g. the Host/Port if SOCKET is an inet socket."))
437
438 (defgeneric size-of-sockaddr (socket)
439   (:documentation "Return the size of a sockaddr object for SOCKET."))