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