uni-events-2.2.2.1: uni events
Safe HaskellNone
LanguageHaskell98

Events.Events

Description

Events and combinators for them.

Synopsis

Documentation

data Result Source #

Constructors

Immediate 
Awaiting (IO ()) 
AwaitingAlways (IO ()) 

newtype Event a Source #

Constructors

Event (Toggle -> (IO a -> IO ()) -> IO Result) 

Instances

Instances details
Monad Event Source # 
Instance details

Defined in Events.Events

Methods

(>>=) :: Event a -> (a -> Event b) -> Event b #

(>>) :: Event a -> Event b -> Event b #

return :: a -> Event a #

Functor Event Source # 
Instance details

Defined in Events.Events

Methods

fmap :: (a -> b) -> Event a -> Event b #

(<$) :: a -> Event b -> Event a #

MonadFail Event Source # 
Instance details

Defined in Events.Events

Methods

fail :: String -> Event a #

Applicative Event Source # 
Instance details

Defined in Events.Events

Methods

pure :: a -> Event a #

(<*>) :: Event (a -> b) -> Event a -> Event b #

liftA2 :: (a -> b -> c) -> Event a -> Event b -> Event c #

(*>) :: Event a -> Event b -> Event b #

(<*) :: Event a -> Event b -> Event a #

HasEvent Event Source # 
Instance details

Defined in Events.Events

Methods

toEvent :: Event a -> Event a Source #

class HasEvent eventType where Source #

HasEvent represents those event-like things which can be converted to an event.

Methods

toEvent :: eventType a -> Event a Source #

Instances

Instances details
HasEvent Event Source # 
Instance details

Defined in Events.Events

Methods

toEvent :: Event a -> Event a Source #

Guard guard => HasEvent (GuardedEvent guard) Source # 
Instance details

Defined in Events.GuardedEvents

Methods

toEvent :: GuardedEvent guard a -> Event a Source #

never :: Event a Source #

The event that never happens

always :: IO a -> Event a Source #

The event that always happens, immediately

sync :: Event a -> IO a Source #

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 b infixl 2 Source #

Attach an action to be done after the event occurs.

(>>>) :: Event a -> IO b -> Event b infixl 2 Source #

Attach an action to be done after the event occurs.

(+>) :: Event a -> Event a -> Event a infixl 1 Source #

Choose between two events. The first one takes priority.

choose :: [Event a] -> Event a Source #

Choose between a list of events.

tryEV :: Event a -> Event (Either SomeException a) Source #

Catch an error if it occurs during an action attached to an event.

computeEvent :: IO (Event a) -> Event a Source #

Construct a new event using an action which is called at each synchronisation

wrapAbort :: IO (Event a, IO ()) -> Event a Source #

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 where Source #

HasSend represents things like channels on which we can send values

Methods

send :: chan a -> a -> Event () Source #

Instances

Instances details
HasSend Channel Source # 
Instance details

Defined in Events.Channels

Methods

send :: Channel a -> a -> Event () Source #

HasSend (GuardedChannel guard) Source # 
Instance details

Defined in Events.GuardedChannels

Methods

send :: GuardedChannel guard a -> a -> Event () Source #

class HasReceive chan where Source #

HasReceive represents things like channels from which we can take values.

Methods

receive :: chan a -> Event a Source #

Instances

Instances details
HasReceive Channel Source # 
Instance details

Defined in Events.Channels

Methods

receive :: Channel a -> Event a Source #

Guard guard => HasReceive (GuardedChannel guard) Source # 
Instance details

Defined in Events.GuardedChannels

Methods

receive :: GuardedChannel guard a -> Event a Source #

sendIO :: HasSend chan => chan a -> a -> IO () Source #

Send a value along a channel (as an IO action)

receiveIO :: HasReceive chan => chan a -> IO a Source #

Get a value from a channel (as an IO action)

allowWhile :: Event () -> Event a -> Event a Source #

allowWhile event1 event2 waits for event2, while handling event1.

data Request a b Source #

Constructors

Request (a -> IO (Event b, IO ())) 

request :: Request a b -> a -> IO b Source #

doRequest :: Request a b -> a -> IO (Event b, IO ()) Source #

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 b Source #

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