Event
s and combinators for them.
- data Result
- newtype Event a = Event (Toggle -> (IO a -> IO ()) -> IO Result)
- class HasEvent eventType where
- never :: Event a
- always :: IO a -> Event a
- sync :: Event a -> IO a
- poll :: Event a -> IO (Maybe a)
- (>>>=) :: Event a -> (a -> IO b) -> Event b
- (>>>) :: Event a -> IO b -> Event b
- (+>) :: Event a -> Event a -> Event a
- choose :: [Event a] -> Event a
- tryEV :: Event a -> Event (Either Exception a)
- computeEvent :: IO (Event a) -> Event a
- wrapAbort :: IO (Event a, IO ()) -> Event a
- noWait :: Event a -> Event ()
- class HasSend chan where
- class HasReceive chan where
- sendIO :: HasSend chan => chan a -> a -> IO ()
- receiveIO :: HasReceive chan => chan a -> IO a
- allowWhile :: Event () -> Event a -> Event a
- data Request a b = Request (a -> IO (Event b, IO ()))
- request :: Request a b -> a -> IO b
- doRequest :: Request a b -> a -> IO (Event b, IO ())
- spawnEvent :: Event () -> IO (IO ())
- getAllQueued :: Event a -> IO [a]
- thenGetEvent :: Event a -> (a -> Event b) -> Event b
- thenEvent :: Event a -> Event b -> Event b
- doneEvent :: a -> Event a
- syncNoWait :: Event a -> IO ()
Documentation
class HasEvent eventType whereSource
HasEvent represents those event-like things which can be converted to an event.
HasEvent Event | |
Guard guard => HasEvent (GuardedEvent guard) |
Synchronise on an event, waiting on it until it happens, then returning the attached value.
poll :: Event a -> IO (Maybe a)Source
Synchronise on an event, but return immediately with Nothing if it can't be satisfied at once.
(>>>=) :: Event a -> (a -> IO b) -> Event bSource
Attach an action to be done after the event occurs.
tryEV :: Event a -> Event (Either Exception a)Source
Catch an error if it occurs during an action attached to an event.
computeEvent :: IO (Event a) -> Event aSource
Construct a new event using an action which is called at each synchronisation
wrapAbort :: IO (Event a, IO ()) -> Event aSource
When we synchronise on wrapAbort preAction preAction is evaluated to yield (event,postAction). Then exactly one of the following: (1) thr event is satisfied, and postAction is not done. (2) some other event in this synchronisation is satisfied (so this one isn't), and postAction is done. (3) no event is satisfied (and so we will deadlock).
noWait :: Event a -> Event ()Source
Turns an event into one which is always satisfied at once but registers the value to be done later. WARNING - only to be used with events without actions attached, as any actions will not get done. noWait is typically used with send events, where we don't want to wait for someone to pick up the value.
class HasSend chan whereSource
HasSend represents things like channels on which we can send values
HasSend Channel | |
HasSend (GuardedChannel guard) |
class HasReceive chan whereSource
HasReceive represents things like channels from which we can take values.
HasReceive Channel | |
Guard guard => HasReceive (GuardedChannel guard) |
receiveIO :: HasReceive chan => chan a -> IO aSource
Get a value from a channel (as an IO action)
allowWhile :: Event () -> Event a -> Event aSource
allowWhile event1 event2 waits for event2, while handling event1.
spawnEvent :: Event () -> IO (IO ())Source
Synchronise on an event in a different thread. The kill action it returns is unsafe since it can cause deadlocks if it occurs at an awkward moment. To avoid this use spawnEvent, if possible.
getAllQueued :: Event a -> IO [a]Source
get all we can get from the event without waiting.
thenGetEvent :: Event a -> (a -> Event b) -> Event bSource
syncNoWait :: Event a -> IO ()Source
Register an event as synchronised but don't wait for it to complete. WARNING - only to be used with events without actions attached, as any actions will not get done. noWait is typically used with send events, where we don't want to wait for someone to pick up the value. synchronise on something without waiting