| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Feather
Synopsis
- type EventHandler i o m = Dispatcher o m -> Dispatcher i m
- data EventState
- class SIM s i m => EventInput s i m
- class HasEvents s where
- lensEvents :: Lens' s EventState
- data Complex a b c
- type Complex2 a b = Complex a b ()
- type Complex3 a b c = Complex a b c
- emptyEventState :: EventState
- addHandler :: forall s i m o. (SIM s i m, EventInput s i m, T o, T m) => EventHandler i o m -> m ()
- runEvent :: SIM s i m => i -> m ()
- getHandler :: forall s i m. SIM s i m => m (i -> m ())
- testEvents :: IO ()
Documentation
type EventHandler i o m = Dispatcher o m -> Dispatcher i m Source #
data EventState Source #
Instances
| HasEvents EventState Source # | Lenses |
Defined in Feather Methods | |
class SIM s i m => EventInput s i m Source #
An event handler may listen for many different types
Minimal complete definition
getInputs
Instances
| SIM s i m => EventInput s i m Source # | |
Defined in Feather Methods getInputs :: T o => EventHandler i o m -> m [InputSpec m] | |
| (SM s m, T a, T b, T c) => EventInput s (Complex a b c) m Source # | |
Defined in Feather Methods getInputs :: T o => EventHandler (Complex a b c) o m -> m [InputSpec m] | |
class HasEvents s where Source #
Types
Methods
lensEvents :: Lens' s EventState Source #
Instances
| HasEvents EventState Source # | Lenses |
Defined in Feather Methods | |
Complex events
Instances
| (SM s m, T a, T b, T c) => EventInput s (Complex a b c) m Source # | |
Defined in Feather Methods getInputs :: T o => EventHandler (Complex a b c) o m -> m [InputSpec m] | |
| (Eq a, Eq b, Eq c) => Eq (Complex a b c) Source # | |
| (Ord a, Ord b, Ord c) => Ord (Complex a b c) Source # | |
Defined in Feather Methods compare :: Complex a b c -> Complex a b c -> Ordering # (<) :: Complex a b c -> Complex a b c -> Bool # (<=) :: Complex a b c -> Complex a b c -> Bool # (>) :: Complex a b c -> Complex a b c -> Bool # (>=) :: Complex a b c -> Complex a b c -> Bool # | |
| (Show a, Show b, Show c) => Show (Complex a b c) Source # | |
addHandler :: forall s i m o. (SIM s i m, EventInput s i m, T o, T m) => EventHandler i o m -> m () Source #
getHandler :: forall s i m. SIM s i m => m (i -> m ()) Source #
Get an event handler from the cache
testEvents :: IO () Source #