0.8.10.70:
[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 #|| <h2>SOCKETs</h2>
7
8 |#
9
10 (eval-when (:load-toplevel :compile-toplevel :execute)
11 (defclass socket ()
12   ((file-descriptor :initarg :descriptor
13                     :reader socket-file-descriptor)
14    (family :initform (error "No socket family") :reader socket-family)
15    (protocol :initarg :protocol :reader socket-protocol)
16    (type  :initarg :type :reader socket-type)
17    (stream))))
18   
19 (defmethod print-object ((object socket) stream)
20   (print-unreadable-object (object stream :type t :identity t)
21                            (princ "descriptor " stream)
22                            (princ (slot-value object 'file-descriptor) stream)))
23
24
25 (defmethod shared-initialize :after ((socket socket) slot-names
26                                      &key protocol type
27                                      &allow-other-keys)
28   (let* ((proto-num
29           (cond ((and protocol (keywordp protocol))
30                  (get-protocol-by-name (string-downcase (symbol-name protocol))))
31                 (protocol protocol)
32                 (t 0)))
33          (fd (or (and (slot-boundp socket 'file-descriptor)
34                       (socket-file-descriptor socket))
35                  (sockint::socket (socket-family socket)
36                                   (ecase type
37                                     ((:datagram) sockint::sock-dgram)
38                                     ((:stream) sockint::sock-stream))
39                                   proto-num))))
40       (if (= fd -1) (socket-error "socket"))
41       (setf (slot-value socket 'file-descriptor) fd
42             (slot-value socket 'protocol) proto-num
43             (slot-value socket 'type) type)
44       (sb-ext:finalize socket (lambda () (sockint::close fd)))))
45
46 \f
47
48 (defgeneric make-sockaddr-for (socket &optional sockaddr &rest address)
49   (:documentation "Return a Socket Address object suitable for use with SOCKET.
50 When SOCKADDR is passed, it is used instead of a new object."))
51
52 (defgeneric free-sockaddr-for (socket sockaddr)
53   (:documentation "Deallocate a Socket Address object that was
54 created for SOCKET."))
55
56 (defmacro with-sockaddr-for ((socket sockaddr &optional sockaddr-args) &body body)
57   `(let ((,sockaddr (apply #'make-sockaddr-for ,socket nil ,sockaddr-args)))
58      (unwind-protect (progn ,@body)
59        (free-sockaddr-for ,socket ,sockaddr))))
60
61 ;; we deliberately redesign the "bind" interface: instead of passing a
62 ;; sockaddr_something as second arg, we pass the elements of one as
63 ;; multiple arguments.
64
65 (defgeneric socket-bind (socket &rest address)
66   (:documentation "Bind SOCKET to ADDRESS, which may vary according to
67 socket family.  For the INET family, pass ADDRESS and PORT as two
68 arguments; for FILE address family sockets, pass the filename string.
69 See also bind(2)"))
70
71 (defmethod socket-bind ((socket socket)
72                         &rest address)
73   (with-sockaddr-for (socket sockaddr address)
74     (if (= (sockint::bind (socket-file-descriptor socket)
75                           sockaddr
76                           (size-of-sockaddr socket))
77            -1)
78         (socket-error "bind"))))
79
80 \f
81 (defgeneric socket-accept (socket)
82   (:documentation "Perform the accept(2) call, returning a
83 newly-created connected socket and the peer address as multiple
84 values"))
85   
86 (defmethod socket-accept ((socket socket))
87   (with-sockaddr-for (socket sockaddr)
88     (let ((fd (sockint::accept (socket-file-descriptor socket)
89                                sockaddr
90                                (size-of-sockaddr socket))))
91       (apply #'values
92              (if (= fd -1)
93                  (socket-error "accept")
94                  (let ((s (make-instance (class-of socket)
95                              :type (socket-type socket)
96                              :protocol (socket-protocol socket)
97                              :descriptor fd)))
98                    (sb-ext:finalize s (lambda () (sockint::close fd)))))
99              (multiple-value-list (bits-of-sockaddr socket sockaddr))))))
100     
101 (defgeneric socket-connect (socket &rest address)
102   (:documentation "Perform the connect(2) call to connect SOCKET to a
103   remote PEER.  No useful return value."))
104
105 (defmethod socket-connect ((socket socket) &rest peer)
106   (with-sockaddr-for (socket sockaddr peer)
107     (if (= (sockint::connect (socket-file-descriptor socket)
108                              sockaddr
109                              (size-of-sockaddr socket))
110            -1)
111         (socket-error "connect"))))
112
113 (defgeneric socket-peername (socket)
114   (:documentation "Return the socket's peer; depending on the address
115   family this may return multiple values"))
116   
117 (defmethod socket-peername ((socket socket))
118   (with-sockaddr-for (socket sockaddr)
119     (when (= (sockint::getpeername (socket-file-descriptor socket)
120                                     sockaddr
121                                     (size-of-sockaddr socket))
122              -1)
123       (socket-error "getpeername"))
124     (bits-of-sockaddr socket sockaddr)))
125
126 (defgeneric socket-name (socket)
127   (:documentation "Return the address (as vector of bytes) and port
128   that the socket is bound to, as multiple values."))
129
130 (defmethod socket-name ((socket socket))
131   (with-sockaddr-for (socket sockaddr)
132     (when (= (sockint::getsockname (socket-file-descriptor socket)
133                                    sockaddr
134                                    (size-of-sockaddr socket))
135              -1)
136       (socket-error "getsockname"))
137     (bits-of-sockaddr socket sockaddr)))
138
139
140 ;;; There are a whole bunch of interesting things you can do with a
141 ;;; socket that don't really map onto "do stream io", especially in
142 ;;; CL which has no portable concept of a "short read".  socket-receive
143 ;;; allows us to read from an unconnected socket into a buffer, and
144 ;;; to learn who the sender of the packet was
145
146 (defgeneric socket-receive (socket buffer length
147                             &key
148                             oob peek waitall element-type)
149   (:documentation "Read LENGTH octets from SOCKET into BUFFER (or a freshly-consed buffer if
150 NIL), using recvfrom(2).  If LENGTH is NIL, the length of BUFFER is
151 used, so at least one of these two arguments must be non-NIL.  If
152 BUFFER is supplied, it had better be of an element type one octet wide.
153 Returns the buffer, its length, and the address of the peer
154 that sent it, as multiple values.  On datagram sockets, sets MSG_TRUNC
155 so that the actual packet length is returned even if the buffer was too
156 small"))
157   
158 (defmethod socket-receive ((socket socket) buffer length
159                            &key
160                            oob peek waitall
161                            (element-type 'character))
162   (with-sockaddr-for (socket sockaddr)
163     (let ((flags
164            (logior (if oob sockint::MSG-OOB 0)
165                    (if peek sockint::MSG-PEEK 0)
166                    (if waitall sockint::MSG-WAITALL 0)
167                    #+linux sockint::MSG-NOSIGNAL ;don't send us SIGPIPE
168                    (if (eql (socket-type socket) :datagram)
169                        sockint::msg-TRUNC 0))))
170       (unless (or buffer length)
171         (error "Must supply at least one of BUFFER or LENGTH"))
172       (unless length
173         (setf length (length buffer)))
174       (let ((copy-buffer (sb-alien:make-alien (array sb-alien:unsigned 1) length)))
175         (unwind-protect
176             (sb-alien:with-alien ((sa-len (array (sb-alien:unsigned 32) 2)))
177               (setf (sb-alien:deref sa-len 0) (size-of-sockaddr socket))
178               (let ((len
179                      (sockint::recvfrom (socket-file-descriptor socket)
180                                         copy-buffer
181                                         length
182                                         flags
183                                         sockaddr
184                                         (sb-alien:cast sa-len (* integer)))))
185                 (when (= len -1) (socket-error "recvfrom"))
186                 (loop for i from 0 below len
187                       do (setf (elt buffer i) (sb-alien:deref copy-buffer i)))
188                 (apply #'values buffer len (multiple-value-list
189                                             (bits-of-sockaddr socket sockaddr)))))
190           (sb-alien:free-alien copy-buffer))))))
191
192
193
194 (defgeneric socket-listen (socket backlog)
195   (:documentation "Mark SOCKET as willing to accept incoming connections.  BACKLOG
196 defines the maximum length that the queue of pending connections may
197 grow to before new connection attempts are refused.  See also listen(2)"))
198
199 (defmethod socket-listen ((socket socket) backlog)
200   (let ((r (sockint::listen (socket-file-descriptor socket) backlog)))
201     (if (= r -1)
202         (socket-error "listen"))))
203
204 (defgeneric socket-close (socket)
205   (:documentation "Close SOCKET.  May throw any kind of error that write(2) would have
206 thrown.  If SOCKET-MAKE-STREAM has been called, calls CLOSE on that
207 stream instead"))
208
209 (defmethod socket-close ((socket socket))
210   ;; the close(2) manual page has all kinds of warning about not
211   ;; checking the return value of close, on the grounds that an
212   ;; earlier write(2) might have returned successfully w/o actually
213   ;; writing the stuff to disk.  It then goes on to define the only
214   ;; possible error return as EBADF (fd isn't a valid open file
215   ;; descriptor).  Presumably this is an oversight and we could also
216   ;; get anything that write(2) would have given us.
217
218   ;; note that if you have a socket _and_ a stream on the same fd, 
219   ;; the socket will avoid doing anything to close the fd in case
220   ;; the stream has done it already - if so, it may have been
221   ;; reassigned to some other file, and closing it would be bad
222
223   (let ((fd (socket-file-descriptor socket)))
224     (cond ((eql fd -1) ; already closed
225            nil)
226           ((slot-boundp socket 'stream)
227            (close (slot-value socket 'stream)) ;; closes fd
228            (setf (slot-value socket 'file-descriptor) -1)
229            (slot-makunbound socket 'stream))
230           (t
231            (sb-ext:cancel-finalization socket)
232            (handler-case
233                (if (= (sockint::close fd) -1)
234                    (socket-error "close"))
235              (bad-file-descriptor-error (c) (declare (ignore c)) nil)
236              (:no-error (c)  (declare (ignore c)) nil))))))
237
238     
239 (defgeneric socket-make-stream (socket  &rest args)
240     (:documentation "Find or create a STREAM that can be used for IO
241 on SOCKET (which must be connected).  ARGS are passed onto
242 SB-SYS:MAKE-FD-STREAM."))
243
244 (defmethod socket-make-stream ((socket socket)  &rest args)
245   (let ((stream
246          (and (slot-boundp socket 'stream) (slot-value socket 'stream))))
247     (unless stream
248       (setf stream (apply #'sb-sys:make-fd-stream
249                           (socket-file-descriptor socket)
250                           :name "a constant string"
251                           args))
252       (setf (slot-value socket 'stream) stream)
253       (sb-ext:cancel-finalization socket))
254     stream))
255
256 \f
257
258 ;;; Error handling
259
260 (define-condition socket-error (error)
261   ((errno :initform nil
262           :initarg :errno  
263           :reader socket-error-errno) 
264    (symbol :initform nil :initarg :symbol :reader socket-error-symbol)
265    (syscall  :initform "outer space" :initarg :syscall :reader socket-error-syscall))
266   (:report (lambda (c s)
267              (let ((num (socket-error-errno c)))
268                (format s "Socket error in \"~A\": ~A (~A)"
269                        (socket-error-syscall c)
270                        (or (socket-error-symbol c) (socket-error-errno c))
271                        #+cmu (sb-unix:get-unix-error-msg num)
272                        #+sbcl (sb-int:strerror num))))))
273
274 ;;; watch out for slightly hacky symbol punning: we use both the value
275 ;;; and the symbol-name of sockint::efoo
276
277 (defmacro define-socket-condition (symbol name)
278   `(progn
279      (define-condition ,name (socket-error)
280        ((symbol :reader socket-error-symbol :initform (quote ,symbol))))
281      (push (cons ,symbol (quote ,name)) *conditions-for-errno*)))
282
283 (defparameter *conditions-for-errno* nil)
284 ;;; this needs the rest of the list adding to it, really.  They also
285 ;;; need
286 ;;; - conditions to be exported in the DEFPACKAGE form
287 ;;; - symbols to be added to constants.ccon
288 ;;; I haven't yet thought of a non-kludgey way of keeping all this in
289 ;;; the same place
290 (define-socket-condition sockint::EADDRINUSE address-in-use-error)
291 (define-socket-condition sockint::EAGAIN interrupted-error)
292 (define-socket-condition sockint::EBADF bad-file-descriptor-error)
293 (define-socket-condition sockint::ECONNREFUSED connection-refused-error)
294 (define-socket-condition sockint::EINTR interrupted-error)
295 (define-socket-condition sockint::EINVAL invalid-argument-error)
296 (define-socket-condition sockint::ENOBUFS no-buffers-error)
297 (define-socket-condition sockint::ENOMEM out-of-memory-error)
298 (define-socket-condition sockint::EOPNOTSUPP operation-not-supported-error)
299 (define-socket-condition sockint::EPERM operation-not-permitted-error)
300 (define-socket-condition sockint::EPROTONOSUPPORT protocol-not-supported-error)
301 (define-socket-condition sockint::ESOCKTNOSUPPORT socket-type-not-supported-error)
302 (define-socket-condition sockint::ENETUNREACH network-unreachable-error)
303
304
305 (defun condition-for-errno (err)
306   (or (cdr (assoc err *conditions-for-errno* :test #'eql)) 'socket-error))
307       
308 #+cmu
309 (defun socket-error (where)
310   ;; Peter's debian/x86 cmucl packages (and sbcl, derived from them)
311   ;; use a direct syscall interface, and have to call UNIX-GET-ERRNO
312   ;; to update the value that unix-errno looks at.  On other CMUCL
313   ;; ports, (UNIX-GET-ERRNO) is not needed and doesn't exist
314   (when (fboundp 'unix::unix-get-errno) (unix::unix-get-errno))
315   (let ((condition (condition-for-errno sb-unix:unix-errno)))
316     (error condition :errno sb-unix:unix-errno  :syscall where)))
317
318 #+sbcl
319 (defun socket-error (where)
320   (let* ((errno  (sb-unix::get-errno))
321          (condition (condition-for-errno errno)))
322     (error condition :errno errno  :syscall where)))
323
324
325 (defgeneric bits-of-sockaddr (socket sockaddr)
326   (:documentation "Return protocol-dependent bits of parameter
327 SOCKADDR, e.g. the Host/Port if SOCKET is an inet socket."))
328
329 (defgeneric size-of-sockaddr (socket)
330   (:documentation "Return the size of a sockaddr object for SOCKET."))