10e12699d5d0f69cddf1f212eff98835cfbb2672
[sbcl.git] / src / code / serve-event.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
9
10 (in-package "SB!IMPL")
11 \f
12 #|
13 ;;;; object set stuff
14
15 ;;; a hashtable from ports to objects. Each entry is a cons (object . set).
16 ;(defvar *port-table* (make-hash-table :test 'eql))
17
18 (defstruct (object-set
19             (:constructor make-object-set
20                           (name &optional
21                                 (default-handler #'default-default-handler)))
22             (:print-object
23              (lambda (s stream)
24                (format stream "#<Object Set ~S>" (object-set-name s)))))
25   name                                  ; Name, for descriptive purposes.
26   (table (make-hash-table :test 'eq))   ; Message-ID or
27                                         ;   xevent-type --> handler fun.
28   default-handler)
29
30 #!+sb-doc
31 (setf (fdocumentation 'make-object-set 'function)
32       "Make an object set for use by a RPC/xevent server. Name is for
33       descriptive purposes only.")
34
35 ;;; If no such operation defined, signal an error.
36 (defun default-default-handler (object)
37   (error "You lose, object: ~S" object))
38
39 ;;; Look up the handler function for a given message ID.
40 (defun object-set-operation (object-set message-id)
41   #!+sb-doc
42   "Return the handler function in Object-Set for the operation specified by
43    Message-ID, if none, NIL is returned."
44   (check-type object-set object-set)
45   (check-type message-id fixnum)
46   (values (gethash message-id (object-set-table object-set))))
47
48 ;;; The setf inverse for Object-Set-Operation.
49 (defun %set-object-set-operation (object-set message-id new-value)
50   (check-type object-set object-set)
51   (check-type message-id fixnum)
52   (setf (gethash message-id (object-set-table object-set)) new-value))
53
54 |#
55 \f
56 ;;;; file descriptor I/O noise
57
58 (defstruct (handler
59             (:constructor make-handler (direction descriptor function)))
60   ;; Reading or writing...
61   (direction nil :type (member :input :output))
62   ;; File descriptor this handler is tied to.
63   (descriptor 0 :type (mod #.sb!unix:fd-setsize))
64
65   active                      ; T iff this handler is running.
66   (function nil :type function) ; Function to call.
67   bogus)                      ; T if this descriptor is bogus.
68 (def!method print-object ((handler handler) stream)
69   (print-unreadable-object (handler stream :type t)
70     (format stream
71             "~A on ~:[~;BOGUS ~]descriptor ~D: ~S"
72             (handler-direction handler)
73             (handler-bogus handler)
74             (handler-descriptor handler)
75             (handler-function handler))))
76
77 (defvar *descriptor-handlers* nil
78   #!+sb-doc
79   "List of all the currently active handlers for file descriptors")
80
81 ;;; Add a new handler to *descriptor-handlers*.
82 (defun add-fd-handler (fd direction function)
83   #!+sb-doc
84   "Arange to call FUNCTION whenever FD is usable. DIRECTION should be
85   either :INPUT or :OUTPUT. The value returned should be passed to
86   SYSTEM:REMOVE-FD-HANDLER when it is no longer needed."
87   (assert (member direction '(:input :output))
88           (direction)
89           "Invalid direction ~S, must be either :INPUT or :OUTPUT" direction)
90   (let ((handler (make-handler direction fd function)))
91     (push handler *descriptor-handlers*)
92     handler))
93
94 ;;; Remove an old handler from *descriptor-handlers*.
95 (defun remove-fd-handler (handler)
96   #!+sb-doc
97   "Removes HANDLER from the list of active handlers."
98   (setf *descriptor-handlers*
99         (delete handler *descriptor-handlers*
100                 :test #'eq)))
101
102 ;;; Search *descriptor-handlers* for any reference to fd, and nuke 'em.
103 (defun invalidate-descriptor (fd)
104   #!+sb-doc
105   "Remove any handers refering to fd. This should only be used when attempting
106   to recover from a detected inconsistancy."
107   (setf *descriptor-handlers*
108         (delete fd *descriptor-handlers*
109                 :key #'handler-descriptor)))
110
111 ;;; Add the handler to *descriptor-handlers* for the duration of BODY.
112 (defmacro with-fd-handler ((fd direction function) &rest body)
113   #!+sb-doc
114   "Establish a handler with SYSTEM:ADD-FD-HANDLER for the duration of BODY.
115    DIRECTION should be either :INPUT or :OUTPUT, FD is the file descriptor to
116    use, and FUNCTION is the function to call whenever FD is usable."
117   (let ((handler (gensym)))
118     `(let (,handler)
119        (unwind-protect
120            (progn
121              (setf ,handler (add-fd-handler ,fd ,direction ,function))
122              ,@body)
123          (when ,handler
124            (remove-fd-handler ,handler))))))
125
126 ;;; First, get a list and mark bad file descriptors. Then signal an error
127 ;;; offering a few restarts.
128 (defun handler-descriptors-error ()
129   (let ((bogus-handlers nil))
130     (dolist (handler *descriptor-handlers*)
131       (unless (or (handler-bogus handler)
132                   (sb!unix:unix-fstat (handler-descriptor handler)))
133         (setf (handler-bogus handler) t)
134         (push handler bogus-handlers)))
135     (restart-case (error "~S ~[have~;has a~:;have~] bad file descriptor~:P."
136                          bogus-handlers (length bogus-handlers))
137       (remove-them () :report "Remove bogus handlers."
138        (setf *descriptor-handlers*
139              (delete-if #'handler-bogus *descriptor-handlers*)))
140       (retry-them () :report "Retry bogus handlers."
141        (dolist (handler bogus-handlers)
142          (setf (handler-bogus handler) nil)))
143       (continue () :report "Go on, leaving handlers marked as bogus."))))
144 \f
145 ;;;; SERVE-ALL-EVENTS, SERVE-EVENT, and friends
146
147 ;;; Break a real timeout into seconds and microseconds.
148 (defun decode-timeout (timeout)
149   (declare (values (or index null) index))
150   (typecase timeout
151     (integer (values timeout 0))
152     (null (values nil 0))
153     (real
154      (multiple-value-bind (q r) (truncate (coerce timeout 'single-float))
155        (declare (type index q) (single-float r))
156        (values q (the index (truncate (* r 1f6))))))
157     (t
158      (error "Timeout is not a real number or NIL: ~S" timeout))))
159
160 ;;; Wait until FD is usable for DIRECTION. The timeout given to serve-event is
161 ;;; recalculated each time through the loop so that WAIT-UNTIL-FD-USABLE will
162 ;;; timeout at the correct time irrespective of how many events are handled in
163 ;;; the meantime.
164 (defun wait-until-fd-usable (fd direction &optional timeout)
165   #!+sb-doc
166   "Wait until FD is usable for DIRECTION. DIRECTION should be either :INPUT or
167   :OUTPUT. TIMEOUT, if supplied, is the number of seconds to wait before giving
168   up."
169   (declare (type (or real null) timeout))
170   (let (usable)
171     (multiple-value-bind (to-sec to-usec) (decode-timeout timeout)
172       (declare (type (or index null) to-sec to-usec))
173       (multiple-value-bind (stop-sec stop-usec)
174           (if to-sec
175               (multiple-value-bind (okay start-sec start-usec)
176                   (sb!unix:unix-gettimeofday)
177                 (declare (ignore okay))
178                 (let ((usec (+ to-usec start-usec))
179                       (sec (+ to-sec start-sec)))
180                   (declare (type (unsigned-byte 31) usec sec))
181                   (if (>= usec 1000000)
182                       (values (1+ sec) (- usec 1000000))
183                       (values sec usec))))
184               (values 0 0))
185         (declare (type (unsigned-byte 31) stop-sec stop-usec))
186         (with-fd-handler (fd direction #'(lambda (fd)
187                                            (declare (ignore fd))
188                                            (setf usable t)))
189           (loop
190             (sub-serve-event to-sec to-usec)
191
192             (when usable
193               (return t))
194
195             (when timeout
196               (multiple-value-bind (okay sec usec) (sb!unix:unix-gettimeofday)
197                 (declare (ignore okay))
198                 (when (or (> sec stop-sec)
199                           (and (= sec stop-sec) (>= usec stop-usec)))
200                   (return nil))
201                 (setq to-sec (- stop-sec sec))
202                 (cond ((> usec stop-usec)
203                        (decf to-sec)
204                        (setq to-usec (- (+ stop-usec 1000000) usec)))
205                       (t
206                        (setq to-usec (- stop-usec usec))))))))))))
207 \f
208 ;;; Wait for up to timeout seconds for an event to happen. Make sure all
209 ;;; pending events are processed before returning.
210 (defun serve-all-events (&optional timeout)
211   #!+sb-doc
212   "SERVE-ALL-EVENTS calls SERVE-EVENT with the specified timeout. If
213   SERVE-EVENT does something (returns T) it loops over SERVE-EVENT with timeout
214   0 until all events have been served. SERVE-ALL-EVENTS returns T if
215   SERVE-EVENT did something and NIL if not."
216   (do ((res nil)
217        (sval (serve-event timeout) (serve-event 0)))
218       ((null sval) res)
219     (setq res t)))
220
221 ;;; Serve a single event.
222 (defun serve-event (&optional timeout)
223   #!+sb-doc
224   "Receive on all ports and Xevents and dispatch to the appropriate handler
225   function. If timeout is specified, server will wait the specified time (in
226   seconds) and then return, otherwise it will wait until something happens.
227   Server returns T if something happened and NIL otherwise."
228   (multiple-value-bind (to-sec to-usec) (decode-timeout timeout)
229     (sub-serve-event to-sec to-usec)))
230
231 ;;; These macros are chunks of code from SUB-SERVE-EVENT. They randomly
232 ;;; reference the READ-FDS and WRITE-FDS Alien variables (which wold be consed
233 ;;; if passed as function arguments.)
234 (eval-when (:compile-toplevel :execute)
235
236 ;;; Initialize the fd-sets for UNIX-SELECT and return the active descriptor
237 ;;; count.
238 (sb!xc:defmacro calc-masks ()
239   '(progn
240      (sb!unix:fd-zero read-fds)
241      (sb!unix:fd-zero write-fds)
242      (let ((count 0))
243        (declare (type index count))
244        (dolist (handler *descriptor-handlers*)
245          (unless (or (handler-active handler)
246                      (handler-bogus handler))
247            (let ((fd (handler-descriptor handler)))
248              (ecase (handler-direction handler)
249                (:input (sb!unix:fd-set fd read-fds))
250                (:output (sb!unix:fd-set fd write-fds)))
251              (when (> fd count)
252                (setf count fd)))))
253        (1+ count))))
254
255 ;;; Call file descriptor handlers according to the readable and writable masks
256 ;;; returned by select.
257 (sb!xc:defmacro call-fd-handler ()
258   '(let ((result nil))
259      (dolist (handler *descriptor-handlers*)
260        (let ((desc (handler-descriptor handler)))
261          (when (ecase (handler-direction handler)
262                  (:input (sb!unix:fd-isset desc read-fds))
263                  (:output (sb!unix:fd-isset desc write-fds)))
264            (unwind-protect
265                (progn
266                  ;; Doesn't work -- ACK
267                  ;(setf (handler-active handler) t)
268                  (funcall (handler-function handler) desc))
269              (setf (handler-active handler) nil))
270            (ecase (handler-direction handler)
271              (:input (sb!unix:fd-clr desc read-fds))
272              (:output (sb!unix:fd-clr desc write-fds)))
273            (setf result t)))
274        result)))
275
276 ) ; EVAL-WHEN
277
278 ;;; When a *periodic-polling-function* is defined the server will not
279 ;;; block for more than the maximum event timeout and will call the
280 ;;; polling function if it does time out. One important use of this
281 ;;; is to periodically call process-yield.
282 (declaim (type (or null function) *periodic-polling-function*))
283 (defvar *periodic-polling-function*
284   #!-mp nil #!+mp #'sb!mp:process-yield)
285 (declaim (type (unsigned-byte 29) *max-event-to-sec* *max-event-to-usec*))
286 (defvar *max-event-to-sec* 1)
287 (defvar *max-event-to-usec* 0)
288
289 ;;; Takes timeout broken into seconds and microseconds.
290 (defun sub-serve-event (to-sec to-usec)
291   (declare (type (or null (unsigned-byte 29)) to-sec to-usec))
292
293   (let ((call-polling-fn nil))
294     (when (and *periodic-polling-function*
295                ;; Enforce a maximum timeout.
296                (or (null to-sec)
297                    (> to-sec *max-event-to-sec*)
298                    (and (= to-sec *max-event-to-sec*)
299                         (> to-usec *max-event-to-usec*))))
300       (setf to-sec *max-event-to-sec*)
301       (setf to-usec *max-event-to-usec*)
302       (setf call-polling-fn t))
303
304     ;; Next, wait for something to happen.
305     (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set))
306                           (write-fds (sb!alien:struct sb!unix:fd-set)))
307       (let ((count (calc-masks)))
308         (multiple-value-bind (value err) (sb!unix:unix-fast-select
309              count
310              (sb!alien:addr read-fds) (sb!alien:addr write-fds)
311              nil to-sec to-usec)
312         
313           ;; Now see what it was (if anything)
314           (cond (value
315                  (cond ((zerop value)
316                         ;; Timed out.
317                         (when call-polling-fn
318                           (funcall *periodic-polling-function*)))
319                        (t
320                         (call-fd-handler))))
321                 ((eql err sb!unix:eintr)
322                  ;; We did an interrupt.
323                  t)
324                 (t
325                  ;; One of the file descriptors is bad.
326                  (handler-descriptors-error)
327                  nil)))))))