Graphics.UI.WxGeneric.Composite
Description
Module to ease composing zero-to-many widgets to a larger composite widget.
- data Composite user
- pickPanel :: Composite user -> Window w
- pickLayout :: Composite user -> Layout
- pickUser :: Composite user -> user
- compose :: (Panel () -> IO (Layout, user)) -> Window w -> [Prop (Composite user)] -> IO (Composite user)
- singleComposite :: Window w -> user -> Composite user
- singleCompositeEx :: Window w -> Layout -> user -> Composite user
- mapPanelAttr :: (forall w. Attr (Window w) attr) -> Attr (Composite user) attr
- forAllChildren :: Attr (Window ()) attr -> (forall w. Attr (Window w) attr) -> Attr (Composite user) attr
- mapUserAttr :: Attr user attr -> Attr (Composite user) attr
- mapInheritedAttr :: Attr super attr -> Attr (CompositeInherit super) attr
- mapEventF :: (to -> from) -> Event from event -> Event to event
- mapPanelEvent :: (forall w. Event (Window w) event) -> Event (Composite user) event
- mapInheritedEvent :: Event super event -> Event (CompositeInherit super) event
- propagateFutureEvents :: (Reactive from, Reactive to) => [EventToken] -> from -> to -> IO ()
- data EventToken
- allEvents :: [EventToken]
- propagateFutureEventsEx :: (t -> Bool) -> fromWidget -> toWidget -> Event fromWidget (t -> IO ()) -> Event toWidget (t -> IO ()) -> IO ()
- propagateWxEvent :: toWindow -> Event toWindow (inEvt -> IO a) -> inEvt -> IO a
- isEnterOrLeave :: EventMouse -> Bool
- isMouseMotion :: EventMouse -> Bool
- isMouseWheel :: EventMouse -> Bool
- class ValuedWidget value widget | widget -> value where
- widgetValue :: Attr widget value
- updateUser :: (user -> user') -> Composite user -> Composite user'
- updateInherited :: (super -> super') -> CompositeInherit super -> CompositeInherit super'
- newtype Inherit super = Inherit {
- unInherit :: super
- type CompositeInherit super = Composite (Inherit super)
Composite type
Data type which contains a composite widget
Instances
| ValuedWidget a (super a) => ValuedWidget a (Composite (Inherit (super a))) | |
| Widget (Composite user) | |
| Reactive (Composite user) | |
| Literate (Composite user) | |
| Dimensions (Composite user) | |
| Colored (Composite user) | |
| Visible (Composite user) | |
| Parent (Composite user) | |
| Bordered (Composite user) | |
| Child (Composite user) | |
| Able (Composite user) | |
| Identity (Composite user) | |
| Sized (Composite user) |
pickPanel :: Composite user -> Window wSource
Contains the widget, which this Composite represent. The term widget is used broadly here. It can either refer to some basic widget, like a text-box, or to a panel containing multiple sub-widgets.
pickLayout :: Composite user -> LayoutSource
compose :: (Panel () -> IO (Layout, user)) -> Window w -> [Prop (Composite user)] -> IO (Composite user)Source
Composes zero-to-many widgets to a larger composite widget
The composite will automatically implement the following classes:
- Widget
- Able
- Bordered
- Child
- Dimensions
- Identity
- Literate
- Parent
- Sized
- Visible
- Reactive (event class)
if the user type = (Inherit x) and x implements one of the following classes, then so will the Composite:
- Items
- Observable
- Selection
- Selections
- Textual
- Commanding (event class)
- Selecting (event class)
- ValuedWidget
if the composite needs to implement more classes it should be done as follows:
type MyComposite = Composite user instance Foo MyComposite where ...
singleComposite :: Window w -> user -> Composite userSource
Encapsulate a single 'Window w' in the composite type
singleCompositeEx :: Window w -> Layout -> user -> Composite userSource
Encapsulate a single 'Window w' in the composite type
Mapping attributes
mapPanelAttr :: (forall w. Attr (Window w) attr) -> Attr (Composite user) attrSource
Used when an attribute should apply to the panel
forAllChildren :: Attr (Window ()) attr -> (forall w. Attr (Window w) attr) -> Attr (Composite user) attrSource
Used when an attribute should apply to the panel and all of its children
mapUserAttr :: Attr user attr -> Attr (Composite user) attrSource
Used when an attribute should apply to the usertype
mapInheritedAttr :: Attr super attr -> Attr (CompositeInherit super) attrSource
Used when an attribute should apply to the inherited usertype
Mapping events
mapEventF :: (to -> from) -> Event from event -> Event to eventSource
Mapping events using a mapper function
mapPanelEvent :: (forall w. Event (Window w) event) -> Event (Composite user) eventSource
Mapping events from the Panel ()
mapInheritedEvent :: Event super event -> Event (CompositeInherit super) eventSource
Mapping events from the inherited usertype
Event propagation
propagateFutureEvents :: (Reactive from, Reactive to) => [EventToken] -> from -> to -> IO ()Source
propagateFutureEvents is an easy to use wrapper around
propagateFutureEvents.
propagateFutureEvents propagates future events from one widget to
another, based on a list of EventTokens. The from widget will
usually be a normal wxHaskell widget or some Composite. The to
widget will usually be a panel or a frame.
data EventToken Source
Arguments
| :: (t -> Bool) | Only propagates events where this function returns true. |
| -> fromWidget | The Window w to propagate from |
| -> toWidget | The Window w to propagate from |
| -> Event fromWidget (t -> IO ()) | From event |
| -> Event toWidget (t -> IO ()) | To Event |
| -> IO () |
Transmit future events from one wxHaskell widget to a
parent-widget. All events, where propagateThisEvent returns
True is propagated to the parent-widget. If False is returned,
then we call Graphics.UI.WX.Events.propagateEvent, so the
form-widgets normal event handling code will recieve the
event. E.g. a button should not propagate click-events to the
parent-widget, but the button should handle the click-event itself.
However, it is essential to note that propagateThisEvent _cannot_
be used to decide if the from-widget should have some events
blocked. It is only usefull for deciding if events should be
propagated to the parent 'Window w'. Even if an event is propagated
to a parent-widget, then the parent-widget's event handling code
may call Graphics.UI.WX.Events.propagateEvent, and then propagate
the event back to the from-widget.
Note that we need two Event inputs, otherwise the fromWidget and toWidget
must be of the same type.
See propagateFutureEvents for an easier to use version of
propagateFutureEventsEx.
propagateWxEvent :: toWindow -> Event toWindow (inEvt -> IO a) -> inEvt -> IO aSource
Propagate an event to a 'Window w'.
Is Some Event
isMouseWheel :: EventMouse -> BoolSource
Other
class ValuedWidget value widget | widget -> value whereSource
Methods
widgetValue :: Attr widget valueSource
An attribute for the value of a widget. The value should have as precise a type as possible. For example a slider should properly have type Attr Slider Int.
Instances
| ValuedWidget a (super a) => ValuedWidget a (Composite (Inherit (super a))) | |
| ValuedWidget a (GenWid a) | |
| ValuedWidget a (ValuedCmds a) |
updateUser :: (user -> user') -> Composite user -> Composite user'Source
updateInherited :: (super -> super') -> CompositeInherit super -> CompositeInherit super'Source
A marker type, which indicates that we want to derive or inherit all wxHaskell type classes possible.
Instances
| ValuedWidget a (super a) => ValuedWidget a (Composite (Inherit (super a))) |
type CompositeInherit super = Composite (Inherit super)Source