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