|
| Graphics.UI.Phooey.WinEvents | | Portability | ??? | | Stability | experimental | | Maintainer | conal@conal.net |
|
|
|
|
|
| Description |
| Wrap window toolkit as Events & Sources
TODO: Move out of phooey
|
|
| Synopsis |
|
| wEvent :: Event ctl (Sink a) -> ctl -> IO (Event a) | | | wEvent_ :: Event ctl Action -> ctl -> IO (Event ()) | | | attrSource :: Event ctl Action -> Attr ctl a -> ctl -> IO (Source a) | | | type InAttr ctl a = ctl -> IO (Source a) | | | type OutAttr ctl a = ctl -> IO (Source (Sink a)) | | | inAttr :: Commanding ctl => Attr ctl a -> InAttr ctl a | | | outAttr :: Attr ctl a -> OutAttr ctl a | | | type WiU a = forall ctl. Reactive ctl => ctl -> a | | | type WiE a = WiU (Event a) | | | type WiS a = WiU (Source a) | | | type WioU a = forall ctl. Window ctl -> IO a | | | type Wio = Win -> IO Layout | | | type WioE a = WioU (Event a) | | | type WioS a = WioU (Source a) | | | mouseE :: String -> (EventMouse -> Maybe a) -> WioE a | | | enter :: WioE () | | | leave :: WioE () | | | inside :: WioS Bool | | | motion :: WioE Point | | | motion' :: WioE (Point, Modifiers) | | | motionDiff :: WioE Vector | | | motionDiff' :: WioE (Vector, Modifiers) | | | leftDown :: WioE Point | | | leftUp :: WioE Point | | | rightDown :: WioE Point | | | rightUp :: WioE Point | | | size :: (Reactive ctl, Sized ctl) => ctl -> IO (Source Size) | | | leftIsDown :: WioS Bool | | | mouse :: WioS Point | | | mbMouse :: WioS (Maybe Point) | | | leftDragAccum :: Vector -> WioS Vector | | | image :: Attr (Window w) (Image ()) | | | arrayImage :: Array Point Color -> Image () | | | type MkCtl ctl a = Win -> [Prop ctl] -> IO (ctl, Attr ctl a) | | | mkMkCtl :: Attr ctl a -> (Win -> [Prop ctl] -> IO ctl) -> MkCtl ctl a | | | type MkIn ctl a = a -> Win -> IO (ctl, (Source a, Source (Sink a))) | | | type MkOut ctl a = Win -> IO (ctl, Source (Sink a)) | | | attrMkIn :: Commanding ctl => MkCtl ctl a -> [Prop ctl] -> MkIn ctl a | | | attrMkOut :: MkCtl ctl a -> [Prop ctl] -> MkOut ctl a | | | | | lookupLTree :: Eq key => key -> LTree key a -> Maybe a | | | lookupLTrees :: Eq key => key -> [LTree key a] -> Maybe a | | | titledItem :: Title a => String -> a -> LTree String a | | | menuEvent :: Window w -> [Prop (Menu ())] -> [(String, Source Bool, a)] -> IO (Menu (), Event a) | | | menuEvent' :: Window w -> Menu () -> [(String, Source Bool, a)] -> IO (Event a) | | | allEnabled :: [(String, a)] -> [(String, Source Bool, a)] | | | menuH :: Window w -> [Prop (Menu ())] -> [LTree String a] -> IO (Menu (), Event a) | | | menuH' :: Window w -> Menu () -> [LTree String a] -> IO (Event a) | | | mkStatus :: Frame w -> [Prop StatusField] -> IO (Sink String) | | | getAttr :: Attr w a -> w -> IO a | | | setAttr :: Attr w a -> w -> Sink a | | | modifyAttr :: Attr w a -> w -> Sink (a -> a) | | | mapAttr' :: String -> (w -> a -> IO b) -> (w -> a -> b -> IO a) -> Attr w a -> Attr w b |
|
|
|
| Events from wxHaskell-style events
|
|
|
| Make an Event out of a wxHaskell-style event, which must be
readable and writeable.
|
|
|
| Like wEvent but for wxHaskell-style events that don't take data.
|
|
|
| Wrap an attribute & control as a value source. Specializes to
inAttr when change == command.
|
|
| Attributes
|
|
|
| Wrapped input attribute
|
|
|
| Wrapped input attribute
|
|
|
| Convert a wxHaskell-style input attribute
|
|
|
| Convert a wxHaskell-style input attribute
|
|
| Window-based computations
|
|
|
| Window-based computations, universal over Reactive types
|
|
|
| Control-based events
|
|
|
| Control-Based sources
|
|
| type WioU a = forall ctl. Window ctl -> IO a | Source |
|
| Window&IO-based computations, universal over widow types
|
|
|
| Consumes container and yield layout
|
|
|
| Control-based events
|
|
|
| Control-Based sources
|
|
| Events
|
|
|
| Filter mouse events
|
|
|
| Mouse enters control
|
|
|
| Mouse leaves control
|
|
|
| Whether the mouse is in the control
|
|
|
| Mouse motion event. Includes wxHaskell motion, enter, leave, and
leftrightmiddle-drag. Simplified version of 'motion\'', which also
includes key Modifiers.
|
|
|
| Mouse motion event. Includes wxHaskell motion, enter, leave, and
leftrightmiddle-drag. Both point and modifiers. See also motion,
which omits modifiers.
|
|
|
| Mouse motion as difference vectors. Simplified from 'motionDiff\''.
|
|
|
| Mouse motion as difference vectors. Includes Modifiers.
|
|
|
| Left button down
|
|
|
| Left button up
|
|
|
| Right button down
|
|
|
| Right button up
|
|
| Sources
|
|
|
|
|
| Whether the left button is down
|
|
|
| Mouse location source. Starts at point zero
|
|
|
| Mouse location source, when in the control
|
|
|
| Accumulation of mouse movements while left-dragging
|
|
| Image display
|
|
|
| Write-only image attribute.
|
|
| arrayImage :: Array Point Color -> Image () | Source |
|
|
| Making widgets with sources & sinks
|
|
|
| Control/widget maker
|
|
|
| More conventional but less general interface to MkCtl
|
|
|
| Make an input control
|
|
|
| Make an output control
|
|
|
| Attribute-based input control
|
|
|
| Attribute-based output control
|
|
| Menus
|
|
|
| Trees with labels at each internal node and leaf, plus data at the leaves.
| | Constructors | | TItem k a | | | TChildren k [LTree k a] | |
| Instances | |
|
|
|
| Find the first item with the given label
|
|
|
|
|
| Titled LTree item. Use name for title and TItem
|
|
|
| Make an event that interfaces as a menu. The bool sources say when
each menu item is enabled
|
|
|
| Like menuEvent, but you supply your own menu to fill.
|
|
|
| Convenience for use with menuEvent. Fill in pure True for
whether-enabled sources.
|
|
|
| Hierarchical menu from
|
|
|
|
| Misc
|
|
|
|
|
| Get attribute. Just a flipped get. Handy for partial application.
|
|
|
| Set a single attribute. Handy for partial application.
|
|
|
| Modify a single attribute. Handy for partial application.
|
|
|
| Variant of mapAttr, in which the functions have access to control
|
|
| Produced by Haddock version 2.1.0 |