Safe Haskell | None |
---|---|
Language | Haskell98 |
Reactive.Banana.WX
- event1 :: w -> Event w (a -> IO ()) -> MomentIO (Event a)
- event0 :: w -> Event w (IO ()) -> MomentIO (Event ())
- behavior :: w -> Attr w a -> MomentIO (Behavior a)
- data Prop' w = forall a . (Attr w a) :== (Behavior a)
- sink :: w -> [Prop' w] -> MomentIO ()
- module Reactive.Banana.Frameworks
- eventText :: TextCtrl w -> MomentIO (Event String)
- behaviorText :: TextCtrl w -> String -> MomentIO (Behavior String)
- eventSelection :: SingleListBox b -> MomentIO (Event Int)
- event1ToAddHandler :: w -> Event w (a -> IO ()) -> IO (AddHandler a)
- event0ToEvent1 :: Event w (IO ()) -> Event w (() -> IO ())
Synopsis
Utility functions for interfacing with wxHaskell. Note: Useful, but I haven't done any serious design work on these.
General
behavior :: w -> Attr w a -> MomentIO (Behavior a) Source
Behavior from an attribute.
Uses fromPoll
, so may behave as you expect.
Variant of wx properties that accept a Behavior
.
module Reactive.Banana.Frameworks
Specific widgets
eventText :: TextCtrl w -> MomentIO (Event String) Source
Event that occurs when the user changed the text in text edit widget.
behaviorText :: TextCtrl w -> String -> MomentIO (Behavior String) Source
Behavior corresponding to user input the text field.
eventSelection :: SingleListBox b -> MomentIO (Event Int) Source
Event that occurs when the user changed the selection marker in a list box widget.
Utilities
event1ToAddHandler :: w -> Event w (a -> IO ()) -> IO (AddHandler a) Source
Obtain an AddHandler
from a Event
.
event0ToEvent1 :: Event w (IO ()) -> Event w (() -> IO ()) Source
Obtain an AddHandler
from a Event
.