| Portability | portable | 
|---|---|
| Stability | provisional | 
| Maintainer | [email protected] | 
Graphics.UI.WXCore.Events
Contents
Description
Dynamically set (and get) Haskell event handlers for basic wxWindows events.
Note that one should always call skipCurrentEvent when an event is not
processed in the event handler so that other eventhandlers can process the
event.
- buttonOnCommand :: Button a -> IO () -> IO ()
- checkBoxOnCommand :: CheckBox a -> IO () -> IO ()
- choiceOnCommand :: Choice a -> IO () -> IO ()
- comboBoxOnCommand :: ComboBox a -> IO () -> IO ()
- comboBoxOnTextEnter :: ComboBox a -> IO () -> IO ()
- controlOnText :: Control a -> IO () -> IO ()
- listBoxOnCommand :: ListBox a -> IO () -> IO ()
- spinCtrlOnCommand :: SpinCtrl a -> IO () -> IO ()
- radioBoxOnCommand :: RadioBox a -> IO () -> IO ()
- sliderOnCommand :: Slider a -> IO () -> IO ()
- textCtrlOnTextEnter :: TextCtrl a -> IO () -> IO ()
- listCtrlOnListEvent :: ListCtrl a -> (EventList -> IO ()) -> IO ()
- treeCtrlOnTreeEvent :: TreeCtrl a -> (EventTree -> IO ()) -> IO ()
- gridOnGridEvent :: Grid a -> (EventGrid -> IO ()) -> IO ()
- windowOnMouse :: Window a -> Bool -> (EventMouse -> IO ()) -> IO ()
- windowOnKeyChar :: Window a -> (EventKey -> IO ()) -> IO ()
- windowOnKeyDown :: Window a -> (EventKey -> IO ()) -> IO ()
- windowOnKeyUp :: Window a -> (EventKey -> IO ()) -> IO ()
- windowAddOnClose :: Window a -> IO () -> IO ()
- windowOnClose :: Window a -> IO () -> IO ()
- windowOnDestroy :: Window a -> IO () -> IO ()
- windowAddOnDelete :: Window a -> IO () -> IO ()
- windowOnDelete :: Window a -> IO () -> IO ()
- windowOnCreate :: Window a -> IO () -> IO ()
- windowOnIdle :: Window a -> IO Bool -> IO ()
- windowOnTimer :: Window a -> IO () -> IO ()
- windowOnSize :: Window a -> IO () -> IO ()
- windowOnFocus :: Window a -> (Bool -> IO ()) -> IO ()
- windowOnActivate :: Window a -> (Bool -> IO ()) -> IO ()
- windowOnPaint :: Window a -> (DC () -> Rect -> IO ()) -> IO ()
- windowOnPaintRaw :: Window a -> (DC () -> Rect -> [Rect] -> IO ()) -> IO ()
- windowOnContextMenu :: Window a -> IO () -> IO ()
- windowOnScroll :: Window a -> (EventScroll -> IO ()) -> IO ()
- htmlWindowOnHtmlEvent :: WXCHtmlWindow a -> Bool -> (EventHtml -> IO ()) -> IO ()
- evtHandlerOnMenuCommand :: EvtHandler a -> Id -> IO () -> IO ()
- evtHandlerOnEndProcess :: EvtHandler a -> (Int -> Int -> IO ()) -> IO ()
- evtHandlerOnInput :: EvtHandler b -> (String -> StreamStatus -> IO ()) -> InputStream a -> Int -> IO ()
- evtHandlerOnInputSink :: EvtHandler b -> (String -> StreamStatus -> IO ()) -> InputSink a -> IO ()
- evtHandlerOnTaskBarIconEvent :: TaskBarIcon a -> (EventTaskBarIcon -> IO ()) -> IO ()
- data  EventSTC - = STCChange
- | STCStyleNeeded
- | STCCharAdded Char Int
- | STCSavePointReached
- | STCSavePointLeft
- | STCROModifyAttempt
- | STCKey
- | STCDoubleClick
- | STCUpdateUI
- | STCModified Int Int (Maybe String) Int Int Int Int Int
- | STCMacroRecord Int Int Int
- | STCMarginClick Bool Bool Bool Int Int
- | STCNeedShown Int Int
- | STCPainted
- | STCUserListSelection Int String
- | STCUriDropped String
- | STCDwellStart Point
- | STCDwellEnd Point
- | STCStartDrag Int Int String
- | STCDragOver Point DragResult
- | STCDoDrop String DragResult
- | STCZoom
- | STCHotspotClick
- | STCHotspotDClick
- | STCCalltipClick
- | STCAutocompSelection
- | STCUnknown
 
- stcOnSTCEvent :: StyledTextCtrl a -> (EventSTC -> IO ()) -> IO ()
- stcGetOnSTCEvent :: StyledTextCtrl a -> IO (EventSTC -> IO ())
- data  EventPrint - = PrintBeginDoc (IO ()) Int Int
- | PrintEndDoc
- | PrintBegin
- | PrintEnd
- | PrintPrepare
- | PrintPage (IO ()) (DC ()) Int
- | PrintUnknown Int
 
- printOutOnPrint :: WXCPrintout a -> (EventPrint -> IO ()) -> IO ()
- buttonGetOnCommand :: Window a -> IO (IO ())
- checkBoxGetOnCommand :: CheckBox a -> IO (IO ())
- choiceGetOnCommand :: Choice a -> IO (IO ())
- comboBoxGetOnCommand :: ComboBox a -> IO (IO ())
- comboBoxGetOnTextEnter :: ComboBox a -> IO (IO ())
- controlGetOnText :: Control a -> IO (IO ())
- listBoxGetOnCommand :: ListBox a -> IO (IO ())
- spinCtrlGetOnCommand :: SpinCtrl a -> IO (IO ())
- radioBoxGetOnCommand :: RadioBox a -> IO (IO ())
- sliderGetOnCommand :: Slider a -> IO (IO ())
- textCtrlGetOnTextEnter :: TextCtrl a -> IO (IO ())
- listCtrlGetOnListEvent :: ListCtrl a -> IO (EventList -> IO ())
- treeCtrlGetOnTreeEvent :: TreeCtrl a -> IO (EventTree -> IO ())
- gridGetOnGridEvent :: Grid a -> IO (EventGrid -> IO ())
- windowGetOnMouse :: Window a -> IO (EventMouse -> IO ())
- windowGetOnKeyChar :: Window a -> IO (EventKey -> IO ())
- windowGetOnKeyDown :: Window a -> IO (EventKey -> IO ())
- windowGetOnKeyUp :: Window a -> IO (EventKey -> IO ())
- windowGetOnClose :: Window a -> IO (IO ())
- windowGetOnDestroy :: Window a -> IO (IO ())
- windowGetOnDelete :: Window a -> IO (IO ())
- windowGetOnCreate :: Window a -> IO (IO ())
- windowGetOnIdle :: Window a -> IO (IO Bool)
- windowGetOnTimer :: Window a -> IO (IO ())
- windowGetOnSize :: Window a -> IO (IO ())
- windowGetOnFocus :: Window a -> IO (Bool -> IO ())
- windowGetOnActivate :: Window a -> IO (Bool -> IO ())
- windowGetOnPaint :: Window a -> IO (DC () -> Rect -> IO ())
- windowGetOnPaintRaw :: Window a -> IO (DC () -> Rect -> [Rect] -> IO ())
- windowGetOnContextMenu :: Window a -> IO (IO ())
- windowGetOnScroll :: Window a -> IO (EventScroll -> IO ())
- htmlWindowGetOnHtmlEvent :: WXCHtmlWindow a -> IO (EventHtml -> IO ())
- evtHandlerGetOnMenuCommand :: EvtHandler a -> Id -> IO (IO ())
- evtHandlerGetOnEndProcess :: EvtHandler a -> IO (Int -> Int -> IO ())
- evtHandlerGetOnInputSink :: EvtHandler b -> IO (String -> StreamStatus -> IO ())
- evtHandlerGetOnTaskBarIconEvent :: EvtHandler a -> Id -> EventTaskBarIcon -> IO (IO ())
- printOutGetOnPrint :: WXCPrintout a -> IO (EventPrint -> IO ())
- windowTimerAttach :: Window a -> IO (Timer ())
- windowTimerCreate :: Window a -> IO (TimerEx ())
- timerOnCommand :: TimerEx a -> IO () -> IO ()
- timerGetOnCommand :: TimerEx a -> IO (IO ())
- appRegisterIdle :: Int -> IO (IO ())
- data  EventCalendar - = CalendarDayChanged (DateTime ())
- | CalendarDoubleClicked (DateTime ())
- | CalendarMonthChanged (DateTime ())
- | CalendarSelectionChanged (DateTime ())
- | CalendarWeekdayClicked Int
- | CalendarYearChanged (DateTime ())
- | CalendarUnknown
 
- calendarCtrlOnCalEvent :: CalendarCtrl a -> (EventCalendar -> IO ()) -> IO ()
- calendarCtrlGetOnCalEvent :: CalendarCtrl a -> IO (EventCalendar -> IO ())
- data StreamStatus
- streamStatusFromInt :: Int -> StreamStatus
- data  Modifiers  = Modifiers {- altDown :: !Bool
- shiftDown :: !Bool
- controlDown :: !Bool
- metaDown :: !Bool
 
- showModifiers :: Modifiers -> String
- noneDown :: Modifiers
- justShift :: Modifiers
- justAlt :: Modifiers
- justControl :: Modifiers
- justMeta :: Modifiers
- isNoneDown :: Modifiers -> Bool
- isNoShiftAltControlDown :: Modifiers -> Bool
- data  EventMouse - = MouseMotion !Point !Modifiers
- | MouseEnter !Point !Modifiers
- | MouseLeave !Point !Modifiers
- | MouseLeftDown !Point !Modifiers
- | MouseLeftUp !Point !Modifiers
- | MouseLeftDClick !Point !Modifiers
- | MouseLeftDrag !Point !Modifiers
- | MouseRightDown !Point !Modifiers
- | MouseRightUp !Point !Modifiers
- | MouseRightDClick !Point !Modifiers
- | MouseRightDrag !Point !Modifiers
- | MouseMiddleDown !Point !Modifiers
- | MouseMiddleUp !Point !Modifiers
- | MouseMiddleDClick !Point !Modifiers
- | MouseMiddleDrag !Point !Modifiers
- | MouseWheel !Bool !Point !Modifiers
 
- showMouse :: EventMouse -> String
- mousePos :: EventMouse -> Point
- mouseModifiers :: EventMouse -> Modifiers
- data EventKey = EventKey !Key !Modifiers !Point
- data  Key - = KeyChar !Char
- | KeyOther !KeyCode
- | KeyBack
- | KeyTab
- | KeyReturn
- | KeyEscape
- | KeySpace
- | KeyDelete
- | KeyInsert
- | KeyEnd
- | KeyHome
- | KeyLeft
- | KeyUp
- | KeyRight
- | KeyDown
- | KeyPageUp
- | KeyPageDown
- | KeyStart
- | KeyClear
- | KeyShift
- | KeyAlt
- | KeyControl
- | KeyMenu
- | KeyPause
- | KeyCapital
- | KeyHelp
- | KeySelect
- | KeyPrint
- | KeyExecute
- | KeySnapshot
- | KeyCancel
- | KeyLeftButton
- | KeyRightButton
- | KeyMiddleButton
- | KeyNum0
- | KeyNum1
- | KeyNum2
- | KeyNum3
- | KeyNum4
- | KeyNum5
- | KeyNum6
- | KeyNum7
- | KeyNum8
- | KeyNum9
- | KeyMultiply
- | KeyAdd
- | KeySeparator
- | KeySubtract
- | KeyDecimal
- | KeyDivide
- | KeyF1
- | KeyF2
- | KeyF3
- | KeyF4
- | KeyF5
- | KeyF6
- | KeyF7
- | KeyF8
- | KeyF9
- | KeyF10
- | KeyF11
- | KeyF12
- | KeyF13
- | KeyF14
- | KeyF15
- | KeyF16
- | KeyF17
- | KeyF18
- | KeyF19
- | KeyF20
- | KeyF21
- | KeyF22
- | KeyF23
- | KeyF24
- | KeyNumLock
- | KeyScroll
 
- keyKey :: EventKey -> Key
- keyModifiers :: EventKey -> Modifiers
- keyPos :: EventKey -> Point
- showKey :: Key -> String
- showKeyModifiers :: Key -> Modifiers -> String
- data  DragResult - = DragError
- | DragNone
- | DragCopy
- | DragMove
- | DragLink
- | DragCancel
- | DragUnknown
 
- dropTargetOnData :: DropTarget a -> (Point -> DragResult -> IO DragResult) -> IO ()
- dropTargetOnDrop :: DropTarget a -> (Point -> IO Bool) -> IO ()
- dropTargetOnEnter :: DropTarget a -> (Point -> DragResult -> IO DragResult) -> IO ()
- dropTargetOnDragOver :: DropTarget a -> (Point -> DragResult -> IO DragResult) -> IO ()
- dropTargetOnLeave :: DropTarget a -> IO () -> IO ()
- data DragMode
- dragAndDrop :: DropSource a -> DragMode -> (DragResult -> IO ()) -> IO ()
- fileDropTarget :: Window a -> (Point -> [String] -> IO ()) -> IO ()
- textDropTarget :: Window a -> TextDataObject b -> (Point -> String -> IO ()) -> IO ()
- data  EventScroll - = ScrollTop !Orientation !Int
- | ScrollBottom !Orientation !Int
- | ScrollLineUp !Orientation !Int
- | ScrollLineDown !Orientation !Int
- | ScrollPageUp !Orientation !Int
- | ScrollPageDown !Orientation !Int
- | ScrollTrack !Orientation !Int
- | ScrollRelease !Orientation !Int
 
- data  Orientation - = Horizontal
- | Vertical
 
- scrollOrientation :: EventScroll -> Orientation
- scrollPos :: EventScroll -> Int
- data  EventTree - = TreeBeginRDrag TreeItem !Point (IO ())
- | TreeBeginDrag TreeItem !Point (IO ())
- | TreeEndDrag TreeItem !Point
- | TreeBeginLabelEdit TreeItem String (IO ())
- | TreeEndLabelEdit TreeItem String Bool (IO ())
- | TreeDeleteItem TreeItem
- | TreeItemActivated TreeItem
- | TreeItemCollapsed TreeItem
- | TreeItemCollapsing TreeItem (IO ())
- | TreeItemExpanding TreeItem (IO ())
- | TreeItemExpanded TreeItem
- | TreeItemRightClick TreeItem
- | TreeItemMiddleClick TreeItem
- | TreeSelChanged TreeItem TreeItem
- | TreeSelChanging TreeItem TreeItem (IO ())
- | TreeKeyDown TreeItem EventKey
- | TreeUnknown
 
- data  EventList - = ListBeginDrag !ListIndex !Point (IO ())
- | ListBeginRDrag !ListIndex !Point (IO ())
- | ListBeginLabelEdit !ListIndex (IO ())
- | ListEndLabelEdit !ListIndex !Bool (IO ())
- | ListDeleteItem !ListIndex
- | ListDeleteAllItems
- | ListItemSelected !ListIndex
- | ListItemDeselected !ListIndex
- | ListItemActivated !ListIndex
- | ListItemFocused !ListIndex
- | ListItemMiddleClick !ListIndex
- | ListItemRightClick !ListIndex
- | ListInsertItem !ListIndex
- | ListColClick !Int
- | ListColRightClick !Int
- | ListColBeginDrag !Int (IO ())
- | ListColDragging !Int
- | ListColEndDrag !Int (IO ())
- | ListKeyDown !Key
- | ListCacheHint !Int !Int
- | ListUnknown
 
- type ListIndex = Int
- data  EventGrid - = GridCellMouse !Row !Column !EventMouse
- | GridLabelMouse !Row !Column !EventMouse
- | GridCellChange !Row !Column !(IO ())
- | GridCellSelect !Row !Column !(IO ())
- | GridCellDeSelect !Row !Column !(IO ())
- | GridEditorHidden !Row !Column !(IO ())
- | GridEditorShown !Row !Column !(IO ())
- | GridEditorCreated !Row !Column (IO (Control ()))
- | GridColSize !Column !Point !Modifiers (IO ())
- | GridRowSize !Row !Point !Modifiers (IO ())
- | GridRangeSelect !Row !Column !Row !Column !Rect !Modifiers !(IO ())
- | GridRangeDeSelect !Row !Column !Row !Column !Rect !Modifiers !(IO ())
- | GridUnknown !Row !Column !Int
 
- type Row = Int
- type Column = Int
- data  EventHtml - = HtmlCellClicked String EventMouse Point
- | HtmlCellHover String
- | HtmlLinkClicked String String String EventMouse Point
- | HtmlSetTitle String
- | HtmlUnknown
 
- data EventTaskBarIcon
- propagateEvent :: IO ()
- skipCurrentEvent :: IO ()
- withCurrentEvent :: (Event () -> IO ()) -> IO ()
- appOnInit :: IO () -> IO ()
- treeCtrlSetItemClientData :: TreeCtrl a -> TreeItem -> IO () -> b -> IO ()
- evtHandlerWithClientData :: EvtHandler a -> b -> ((b -> IO ()) -> IO b -> IO c) -> IO c
- evtHandlerSetClientData :: EvtHandler a -> IO () -> b -> IO ()
- objectWithClientData :: WxObject a -> b -> ((b -> IO ()) -> IO b -> IO c) -> IO c
- objectSetClientData :: WxObject a -> IO () -> b -> IO ()
- inputSinkEventLastString :: InputSinkEvent a -> IO String
- type KeyCode = Int
- modifiersToAccelFlags :: Modifiers -> Int
- keyCodeToKey :: KeyCode -> Key
- keyToKeyCode :: Key -> KeyCode
- windowOnEvent :: Window a -> [EventId] -> handler -> (Event () -> IO ()) -> IO ()
- windowOnEventEx :: Window a -> [EventId] -> handler -> (Bool -> IO ()) -> (Event () -> IO ()) -> IO ()
- type OnEvent = (Bool -> IO ()) -> (Event () -> IO ()) -> IO ()
- evtHandlerOnEvent :: EvtHandler a -> Id -> Id -> [EventId] -> handler -> OnEvent
- evtHandlerOnEventConnect :: EvtHandler a -> Id -> Id -> [EventId] -> state -> OnEvent
- unsafeTreeCtrlGetItemClientData :: TreeCtrl a -> TreeItem -> IO (Maybe b)
- unsafeEvtHandlerGetClientData :: EvtHandler a -> IO (Maybe b)
- unsafeObjectGetClientData :: WxObject a -> IO (Maybe b)
- unsafeGetHandlerState :: EvtHandler a -> Id -> EventId -> b -> IO b
- unsafeWindowGetHandlerState :: Window a -> EventId -> b -> IO b
Set event handlers
Controls
buttonOnCommand :: Button a -> IO () -> IO ()
Set an event handler for a push button.
checkBoxOnCommand :: CheckBox a -> IO () -> IO ()
Set an event handler for when a checkbox clicked.
choiceOnCommand :: Choice a -> IO () -> IO ()
Set an event handler for when a choice item is (de)selected.
comboBoxOnCommand :: ComboBox a -> IO () -> IO ()
Set an event handler for when a combo box item is selected.
comboBoxOnTextEnter :: ComboBox a -> IO () -> IO ()
Set an event handler for an enter command in a combo box.
controlOnText :: Control a -> IO () -> IO ()
Set an event handler for updated text, works for example on a TextCtrl and ComboBox.
listBoxOnCommand :: ListBox a -> IO () -> IO ()
Set an event handler for when a listbox item is (de)selected.
spinCtrlOnCommand :: SpinCtrl a -> IO () -> IO ()
Set an event handler for when a spinCtrl clicked.
radioBoxOnCommand :: RadioBox a -> IO () -> IO ()
Set an event handler for when a radiobox item is selected.
sliderOnCommand :: Slider a -> IO () -> IO ()
Set an event handler for when a slider item changes.
textCtrlOnTextEnter :: TextCtrl a -> IO () -> IO ()
Set an event handler for an enter command in a text control.
listCtrlOnListEvent :: ListCtrl a -> (EventList -> IO ()) -> IO ()
Set a list event handler.
treeCtrlOnTreeEvent :: TreeCtrl a -> (EventTree -> IO ()) -> IO ()
Set a tree event handler.
gridOnGridEvent :: Grid a -> (EventGrid -> IO ()) -> IO ()
Set a grid event handler.
Windows
windowOnMouse :: Window a -> Bool -> (EventMouse -> IO ()) -> IO ()
Set a mouse event handler for a window. The first argument determines whether
 mouse motion events (MouseMotion) are handled or not.
windowOnKeyChar :: Window a -> (EventKey -> IO ()) -> IO ()
Set an event handler for translated key presses.
windowOnKeyDown :: Window a -> (EventKey -> IO ()) -> IO ()
Set an event handler for untranslated key presses. If skipCurrentEvent is not
 called, the corresponding windowOnKeyChar eventhandler won't be called.
windowOnKeyUp :: Window a -> (EventKey -> IO ()) -> IO ()
Set an event handler for (untranslated) key releases.
windowAddOnClose :: Window a -> IO () -> IO ()
Adds a close handler to the currently installed close handlers.
windowOnClose :: Window a -> IO () -> IO ()
Set an event handler that is called when the user tries to close a frame or dialog.
 Don't forget to call the previous handler or frameDestroy explicitly or otherwise the
 frame won't be closed.
windowOnDestroy :: Window a -> IO () -> IO ()
Set an event handler that is called when the window is destroyed. Note: does not seem to work on windows.
windowAddOnDelete :: Window a -> IO () -> IO ()
Add a delete-event handler to the current installed delete-event handlers.
 windowAddOnDelete window new
   = do prev <- windowGetOnDelete window
        windowOnDelete window (do{ new; prev })
windowOnDelete :: Window a -> IO () -> IO ()
Set an event handler that is called when the window is deleted. Use with care as the window itself is in a deletion state.
windowOnCreate :: Window a -> IO () -> IO ()
Set an event handler that is called when the window is created.
windowOnIdle :: Window a -> IO Bool -> IO ()
An idle event is generated in idle time. The handler should return whether more
 idle processing is needed (True) or otherwise the event loop goes into a passive
 waiting state.
windowOnTimer :: Window a -> IO () -> IO ()
A timer event is generated by an attached timer, see windowTimerAttach.
 Broken! (use timerOnCommand instead).
windowOnSize :: Window a -> IO () -> IO ()
Set an event handler that is called when the window is resized.
windowOnFocus :: Window a -> (Bool -> IO ()) -> IO ()
Set an event handler that is called when the window gets or loses the focus.
 The event parameter is True when the window gets the focus.
windowOnActivate :: Window a -> (Bool -> IO ()) -> IO ()
Set an event handler that is called when the window is activated or deactivated.
 The event parameter is True when the window is activated.
windowOnPaint :: Window a -> (DC () -> Rect -> IO ()) -> IO ()
Set an event handler for paint events. The implementation uses an 
 intermediate buffer for non-flickering redraws. 
 The device context (DC)
 is always cleared before the paint handler is called. The paint handler
 also gets the currently visible view area as an argument (adjusted for scrolling).
 Note: you can not set both a windowOnPaintRaw and windowOnPaint handler!
windowOnPaintRaw :: Window a -> (DC () -> Rect -> [Rect] -> IO ()) -> IO ()
Set an event handler for raw paint events. Draws directly to the
 paint device context (PaintDC) and the DC is not cleared when the handler
 is called. The handler takes two other arguments: the view rectangle and a
 list of dirty rectangles. The rectangles contain logical coordinates and
 are already adjusted for scrolled windows.
 Note: you can not set both a windowOnPaintRaw and windowOnPaint handler!
windowOnContextMenu :: Window a -> IO () -> IO ()
A context menu event is generated when the user righ-clicks in a window or presses shift-F10.
windowOnScroll :: Window a -> (EventScroll -> IO ()) -> IO ()
Set a scroll event handler.
htmlWindowOnHtmlEvent :: WXCHtmlWindow a -> Bool -> (EventHtml -> IO ()) -> IO ()
Set a html event handler for a html window. The first argument determines whether
 hover events (HtmlCellHover) are handled or not.
Event handlers
evtHandlerOnMenuCommand :: EvtHandler a -> Id -> IO () -> IO ()
A menu event is generated when the user selects a menu item. You should install this handler on the window that owns the menubar or a popup menu.
evtHandlerOnEndProcess :: EvtHandler a -> (Int -> Int -> IO ()) -> IO ()
Called when a process is ended with the process pid and exitcode.
evtHandlerOnInput :: EvtHandler b -> (String -> StreamStatus -> IO ()) -> InputStream a -> Int -> IO ()
Install an event handler on an input stream. The handler is called whenever input is read (or when an error occurred). The third parameter gives the size of the input batches. The orignal input stream should no longer be referenced after this call!
evtHandlerOnInputSink :: EvtHandler b -> (String -> StreamStatus -> IO ()) -> InputSink a -> IO ()
Install an event handler on a specific input sink. It is advised to
 use the evtHandlerOnInput whenever retrieval of the handler is not necessary.
evtHandlerOnTaskBarIconEvent :: TaskBarIcon a -> (EventTaskBarIcon -> IO ()) -> IO ()
Set a taskbar icon event handler.
Raw STC export
data EventSTC
Scintilla events. * Means extra information is available (excluding position, key and modifiers) but not yet implemented. ! means it's done
Constructors
| STCChange | ! wxEVT_STC_CHANGE. | 
| STCStyleNeeded | ! wxEVT_STC_STYLENEEDED. | 
| STCCharAdded Char Int | ? wxEVT_STC_CHARADDED. The position seems to be broken | 
| STCSavePointReached | ! wxEVT_STC_SAVEPOINTREACHED. | 
| STCSavePointLeft | ! wxEVT_STC_SAVEPOINTLEFT. | 
| STCROModifyAttempt | ! wxEVT_STC_ROMODIFYATTEMPT. | 
| STCKey | 
 | 
| STCDoubleClick | ! wxEVT_STC_DOUBLECLICK. | 
| STCUpdateUI | ! wxEVT_STC_UPDATEUI. | 
| STCModified Int Int (Maybe String) Int Int Int Int Int | ? wxEVT_STC_MODIFIED. | 
| STCMacroRecord Int Int Int | ! wxEVT_STC_MACRORECORD iMessage wParam lParam | 
| STCMarginClick Bool Bool Bool Int Int | ? wxEVT_STC_MARGINCLICK. kolmodin 20050304: Add something nicer for alt, shift and ctrl? Perhaps a new datatype or a tuple. | 
| STCNeedShown Int Int | ! wxEVT_STC_NEEDSHOWN length position. | 
| STCPainted | ! wxEVT_STC_PAINTED. | 
| STCUserListSelection Int String | ! wxEVT_STC_USERLISTSELECTION listType text | 
| STCUriDropped String | ! wxEVT_STC_URIDROPPED | 
| STCDwellStart Point | ! wxEVT_STC_DWELLSTART | 
| STCDwellEnd Point | ! wxEVT_STC_DWELLEND | 
| STCStartDrag Int Int String | ! wxEVT_STC_START_DRAG. | 
| STCDragOver Point DragResult | ! wxEVT_STC_DRAG_OVER | 
| STCDoDrop String DragResult | ! wxEVT_STC_DO_DROP | 
| STCZoom | ! wxEVT_STC_ZOOM | 
| STCHotspotClick | ! wxEVT_STC_HOTSPOT_CLICK | 
| STCHotspotDClick | ! wxEVT_STC_HOTSPOT_DCLICK | 
| STCCalltipClick | ! wxEVT_STC_CALLTIP_CLICK | 
| STCAutocompSelection | ! wxEVT_STC_AUTOCOMP_SELECTION | 
| STCUnknown | Unknown event. Should never occur. | 
Instances
| Show EventSTC | 
stcOnSTCEvent :: StyledTextCtrl a -> (EventSTC -> IO ()) -> IO ()
stcGetOnSTCEvent :: StyledTextCtrl a -> IO (EventSTC -> IO ())
Print events
data EventPrint
Printer events.
Constructors
| PrintBeginDoc (IO ()) Int Int | Print a copy: cancel, start page, end page | 
| PrintEndDoc | |
| PrintBegin | Begin a print job. | 
| PrintEnd | |
| PrintPrepare | Prepare: chance to call  | 
| PrintPage (IO ()) (DC ()) Int | Print a page: cancel, printer device context, page number. | 
| PrintUnknown Int | Unknown print event with event code | 
printOutOnPrint :: WXCPrintout a -> (EventPrint -> IO ()) -> IO ()
Set an event handler for printing.
Get event handlers
Controls
buttonGetOnCommand :: Window a -> IO (IO ())
Get the current button event handler on a window.
checkBoxGetOnCommand :: CheckBox a -> IO (IO ())
Get the current check box event handler.
choiceGetOnCommand :: Choice a -> IO (IO ())
Get the current choice command event handler.
comboBoxGetOnCommand :: ComboBox a -> IO (IO ())
Get the current combo box event handler for selections
comboBoxGetOnTextEnter :: ComboBox a -> IO (IO ())
Get the current text enter event handler.
controlGetOnText :: Control a -> IO (IO ())
Get the current event handler for updated text.
listBoxGetOnCommand :: ListBox a -> IO (IO ())
Get the current listbox event handler for selections.
spinCtrlGetOnCommand :: SpinCtrl a -> IO (IO ())
Get the current check box event handler.
radioBoxGetOnCommand :: RadioBox a -> IO (IO ())
Get the current radio box command handler.
sliderGetOnCommand :: Slider a -> IO (IO ())
Get the current slider command event handler.
textCtrlGetOnTextEnter :: TextCtrl a -> IO (IO ())
Get the current text enter event handler.
listCtrlGetOnListEvent :: ListCtrl a -> IO (EventList -> IO ())
Get the current list event handler of a window.
treeCtrlGetOnTreeEvent :: TreeCtrl a -> IO (EventTree -> IO ())
Get the current tree event handler of a window.
gridGetOnGridEvent :: Grid a -> IO (EventGrid -> IO ())
Get the current grid event handler of a window.
Windows
windowGetOnMouse :: Window a -> IO (EventMouse -> IO ())
Get the current mouse event handler of a window.
windowGetOnKeyChar :: Window a -> IO (EventKey -> IO ())
Get the current translated key handler of a window.
windowGetOnKeyDown :: Window a -> IO (EventKey -> IO ())
Get the current key down handler of a window.
windowGetOnKeyUp :: Window a -> IO (EventKey -> IO ())
Get the current key release handler of a window.
windowGetOnClose :: Window a -> IO (IO ())
Get the current close event handler.
windowGetOnDestroy :: Window a -> IO (IO ())
Get the current destroy event handler.
windowGetOnDelete :: Window a -> IO (IO ())
Get the current delete event handler.
windowGetOnCreate :: Window a -> IO (IO ())
Get the current create event handler.
windowGetOnIdle :: Window a -> IO (IO Bool)
Get the current context menu event handler.
windowGetOnTimer :: Window a -> IO (IO ())
Get the current timer handler.
windowGetOnSize :: Window a -> IO (IO ())
Get the current resize event handler.
windowGetOnFocus :: Window a -> IO (Bool -> IO ())
Get the current focus event handler.
windowGetOnActivate :: Window a -> IO (Bool -> IO ())
Get the current activate event handler.
windowGetOnPaint :: Window a -> IO (DC () -> Rect -> IO ())
Get the current paint event handler.
windowGetOnPaintRaw :: Window a -> IO (DC () -> Rect -> [Rect] -> IO ())
Get the current raw paint event handler.
windowGetOnContextMenu :: Window a -> IO (IO ())
Get the current context menu event handler.
windowGetOnScroll :: Window a -> IO (EventScroll -> IO ())
Get the current scroll event handler of a window.
htmlWindowGetOnHtmlEvent :: WXCHtmlWindow a -> IO (EventHtml -> IO ())
Get the current html event handler of a html window.
Event handlers
evtHandlerGetOnMenuCommand :: EvtHandler a -> Id -> IO (IO ())
Get the current event handler for a certain menu.
evtHandlerGetOnEndProcess :: EvtHandler a -> IO (Int -> Int -> IO ())
Retrieve the current end process handler.
evtHandlerGetOnInputSink :: EvtHandler b -> IO (String -> StreamStatus -> IO ())
Retrieve the current input stream handler.
evtHandlerGetOnTaskBarIconEvent :: EvtHandler a -> Id -> EventTaskBarIcon -> IO (IO ())
Get the current event handler for a taskbar icon.
Printing
printOutGetOnPrint :: WXCPrintout a -> IO (EventPrint -> IO ())
Get the current print handler
Timers
windowTimerAttach :: Window a -> IO (Timer ())
Create a new Timer that is attached to a window. It is automatically deleted when
 its owner is deleted (using windowAddOnDelete). The owning window will receive
 timer events (windowOnTimer). Broken! (use 'windowTimerCreate'\/'timerOnCommand' instead.)
windowTimerCreate :: Window a -> IO (TimerEx ())
Create a new TimerEx timer. It is automatically deleted when its owner is deleted
 (using windowAddOnDelete). React to timer events using timerOnCommand.
timerOnCommand :: TimerEx a -> IO () -> IO ()
Set an event handler that is called on a timer tick. This works for TimerEx
 objects.
timerGetOnCommand :: TimerEx a -> IO (IO ())
Get the current timer event handler.
appRegisterIdle :: Int -> IO (IO ())
appRegisterIdle interval handler registers a global idle event 
 handler that is at least called every interval milliseconds (and
 possible more). Returns a method that can be used to unregister this
 handler (so that it doesn't take any resources anymore). Multiple
 calls to this method chains the different idle event handlers.
Calenders
data EventCalendar
Constructors
calendarCtrlOnCalEvent :: CalendarCtrl a -> (EventCalendar -> IO ()) -> IO ()
Set a calendar event handler.
calendarCtrlGetOnCalEvent :: CalendarCtrl a -> IO (EventCalendar -> IO ())
Get the current calendar event handler of a window.
Types
Streams
data StreamStatus
The status of a stream (see StreamBase)
Constructors
| StreamOk | No error. | 
| StreamEof | No more input. | 
| StreamReadError | Read error. | 
| StreamWriteError | Write error. | 
Instances
| Eq StreamStatus | |
| Show StreamStatus | 
streamStatusFromInt :: Int -> StreamStatus
Convert a stream status code into StreamStatus.
Modifiers
data Modifiers
The Modifiers indicate the meta keys that have been pressed (True) or not (False).
Constructors
| Modifiers | |
| Fields 
 | |
showModifiers :: Modifiers -> String
Show modifiers, for example for use in menus.
Construct a Modifiers structure with just Ctrl meta key pressed.
isNoneDown :: Modifiers -> Bool
Test if no meta key was pressed.
isNoShiftAltControlDown :: Modifiers -> Bool
Test if no shift, alt, or control key was pressed.
Mouse events
data EventMouse
Mouse events. The Point gives the logical (unscrolled) position.
Constructors
| MouseMotion !Point !Modifiers | Mouse was moved over the client area of the window | 
| MouseEnter !Point !Modifiers | Mouse enters in the client area of the window | 
| MouseLeave !Point !Modifiers | Mouse leaves the client area of the window | 
| MouseLeftDown !Point !Modifiers | Mouse left button goes down | 
| MouseLeftUp !Point !Modifiers | Mouse left button goes up | 
| MouseLeftDClick !Point !Modifiers | Mouse left button double click | 
| MouseLeftDrag !Point !Modifiers | Mouse left button drag | 
| MouseRightDown !Point !Modifiers | Mouse right button goes down | 
| MouseRightUp !Point !Modifiers | Mouse right button goes up | 
| MouseRightDClick !Point !Modifiers | Mouse right button double click | 
| MouseRightDrag !Point !Modifiers | Mouse right button drag (unsupported on most platforms) | 
| MouseMiddleDown !Point !Modifiers | Mouse middle button goes down | 
| MouseMiddleUp !Point !Modifiers | Mouse middle button goes up | 
| MouseMiddleDClick !Point !Modifiers | Mouse middle button double click | 
| MouseMiddleDrag !Point !Modifiers | Mouse middle button drag (unsupported on most platforms) | 
| MouseWheel !Bool !Point !Modifiers | Mouse wheel rotation. (Bool is True for a downward rotation) | 
Instances
| Eq EventMouse | |
| Show EventMouse | 
showMouse :: EventMouse -> String
Show an EventMouse in a user friendly way.
mousePos :: EventMouse -> Point
Extract the position from a MouseEvent.
mouseModifiers :: EventMouse -> Modifiers
Extract the modifiers from a MouseEvent.
Keyboard events
data EventKey
A keyboard event contains the key, the modifiers and the focus point.
data Key
A Key represents a single key on a keyboard.
Constructors
keyModifiers :: EventKey -> Modifiers
Extract the modifiers from a keyboard event.
showKeyModifiers :: Key -> Modifiers -> String
Show a key/modifiers combination, for example for use in menus.
Set event handlers
Drop Target events
data DragResult
Drag results
Constructors
| DragError | |
| DragNone | |
| DragCopy | |
| DragMove | |
| DragLink | |
| DragCancel | |
| DragUnknown | 
Instances
| Eq DragResult | |
| Show DragResult | 
dropTargetOnData :: DropTarget a -> (Point -> DragResult -> IO DragResult) -> IO ()
Set an event handler that is called when the drop target can be filled with data.
 This function require to use dropTargetGetData in your event handler to fill data.
dropTargetOnDrop :: DropTarget a -> (Point -> IO Bool) -> IO ()
Set an event handler for an drop command in a drop target.
dropTargetOnEnter :: DropTarget a -> (Point -> DragResult -> IO DragResult) -> IO ()
Set an event handler for an enter command in a drop target.
dropTargetOnDragOver :: DropTarget a -> (Point -> DragResult -> IO DragResult) -> IO ()
Set an event handler for a drag over command in a drop target.
dropTargetOnLeave :: DropTarget a -> IO () -> IO ()
Set an event handler for a leave command in a drop target.
On DragAndDropEvent
dragAndDrop :: DropSource a -> DragMode -> (DragResult -> IO ()) -> IO ()
Set an event handler for a drag & drop command between drag source window and drop
 target. You must set dropTarget before use this action.
 And If you use fileDropTarget or textDropTarget, you need not use this.
Special handler for Drop File event
fileDropTarget :: Window a -> (Point -> [String] -> IO ()) -> IO ()
Set an event handler that is called when files are dropped in target window.
Special handler for Drop Text event
textDropTarget :: Window a -> TextDataObject b -> (Point -> String -> IO ()) -> IO ()
Set an event handler that is called when text is dropped in target window.
Scroll events
data EventScroll
Scroll events.
Constructors
| ScrollTop !Orientation !Int | scroll to top | 
| ScrollBottom !Orientation !Int | scroll to bottom | 
| ScrollLineUp !Orientation !Int | scroll line up | 
| ScrollLineDown !Orientation !Int | scroll line down | 
| ScrollPageUp !Orientation !Int | scroll page up | 
| ScrollPageDown !Orientation !Int | scroll page down | 
| ScrollTrack !Orientation !Int | frequent event when user drags the thumbtrack | 
| ScrollRelease !Orientation !Int | thumbtrack is released | 
Instances
| Show EventScroll | 
data Orientation
The orientation of a widget.
Constructors
| Horizontal | |
| Vertical | 
Instances
| Eq Orientation | |
| Show Orientation | 
scrollOrientation :: EventScroll -> Orientation
Get the orientation of a scroll event.
scrollPos :: EventScroll -> Int
Get the position of the scroll bar.
Tree control events
data EventTree
Tree control events
Constructors
| TreeBeginRDrag TreeItem !Point (IO ()) | Drag with right button. Call  | 
| TreeBeginDrag TreeItem !Point (IO ()) | |
| TreeEndDrag TreeItem !Point | |
| TreeBeginLabelEdit TreeItem String (IO ()) | Edit a label. Call  | 
| TreeEndLabelEdit TreeItem String Bool (IO ()) | End edit.  | 
| TreeDeleteItem TreeItem | |
| TreeItemActivated TreeItem | |
| TreeItemCollapsed TreeItem | |
| TreeItemCollapsing TreeItem (IO ()) | Call the  | 
| TreeItemExpanding TreeItem (IO ()) | Call the  | 
| TreeItemExpanded TreeItem | |
| TreeItemRightClick TreeItem | |
| TreeItemMiddleClick TreeItem | |
| TreeSelChanged TreeItem TreeItem | |
| TreeSelChanging TreeItem TreeItem (IO ()) | Call the  | 
| TreeKeyDown TreeItem EventKey | |
| TreeUnknown | 
List control events
data EventList
List control events.
Constructors
| ListBeginDrag !ListIndex !Point (IO ()) | Drag with left mouse button. Call  | 
| ListBeginRDrag !ListIndex !Point (IO ()) | Drag with right mouse button.  | 
| ListBeginLabelEdit !ListIndex (IO ()) | Edit label. Call  | 
| ListEndLabelEdit !ListIndex !Bool (IO ()) | End editing label.  | 
| ListDeleteItem !ListIndex | |
| ListDeleteAllItems | |
| ListItemSelected !ListIndex | |
| ListItemDeselected !ListIndex | |
| ListItemActivated !ListIndex | Activate (ENTER or double click) | 
| ListItemFocused !ListIndex | |
| ListItemMiddleClick !ListIndex | |
| ListItemRightClick !ListIndex | |
| ListInsertItem !ListIndex | |
| ListColClick !Int | Column has been clicked. (-1 when clicked in control header outside any column) | 
| ListColRightClick !Int | |
| ListColBeginDrag !Int (IO ()) | Column is dragged. Index is of the column left of the divider that is being dragged. Call  | 
| ListColDragging !Int | |
| ListColEndDrag !Int (IO ()) | Column has been dragged. Call  | 
| ListKeyDown !Key | |
| ListCacheHint !Int !Int | (Inclusive) range of list items that are advised to be cached. | 
| ListUnknown | 
type ListIndex = Int
Type synonym for documentation purposes.
Grid control events
data EventGrid
Grid events.
Constructors
| GridCellMouse !Row !Column !EventMouse | |
| GridLabelMouse !Row !Column !EventMouse | |
| GridCellChange !Row !Column !(IO ()) | |
| GridCellSelect !Row !Column !(IO ()) | |
| GridCellDeSelect !Row !Column !(IO ()) | |
| GridEditorHidden !Row !Column !(IO ()) | |
| GridEditorShown !Row !Column !(IO ()) | |
| GridEditorCreated !Row !Column (IO (Control ())) | |
| GridColSize !Column !Point !Modifiers (IO ()) | |
| GridRowSize !Row !Point !Modifiers (IO ()) | |
| GridRangeSelect !Row !Column !Row !Column !Rect !Modifiers !(IO ()) | |
| GridRangeDeSelect !Row !Column !Row !Column !Rect !Modifiers !(IO ()) | |
| GridUnknown !Row !Column !Int | 
type Row = Int
type Column = Int
Html window events
data EventHtml
Html window events
Constructors
| HtmlCellClicked String EventMouse Point | A cell is clicked. Contains the cell id attribute value, the mouse event and the logical coordinates. | 
| HtmlCellHover String | The mouse hovers over a cell. Contains the cell id attribute value. | 
| HtmlLinkClicked String String String EventMouse Point | A link is clicked. Contains the hyperlink, the frame target, the cell id attribute value, the mouse event, and the logical coordinates. | 
| HtmlSetTitle String | Called when a  | 
| HtmlUnknown | Unrecognised html event | 
Instances
| Show EventHtml | 
TaskBar icon events
data EventTaskBarIcon
Constructors
| TaskBarIconMove | |
| TaskBarIconLeftDown | |
| TaskBarIconLeftUp | |
| TaskBarIconRightDown | |
| TaskBarIconRightUp | |
| TaskBarIconLeftDClick | |
| TaskBarIconRightDClick | |
| TaskBarIconUnknown | 
Instances
| Eq EventTaskBarIcon | |
| Show EventTaskBarIcon | 
Current event
propagateEvent :: IO ()
Pass the event on the next wxWindows event handler, either on this window or its parent.
 Always call this method when you do not process the event. (This function just call skipCurrentEvent).
skipCurrentEvent :: IO ()
Pass the event on the next wxWindows event handler, either on this window or its parent.
 Always call this method when you do not process the event. Note: The use of
 propagateEvent is encouraged as it is a much better name than skipCurrentEvent. This
 function name is just for better compatibility with wxWindows :-)
withCurrentEvent :: (Event () -> IO ()) -> IO ()
Do something with the current event if we are calling from an event handler.
Primitive
appOnInit :: IO () -> IO ()
Installs an init handler and starts the event loop. Note: the closure is deleted when initialization is complete, and than the Haskell init function is started.
Client data
treeCtrlSetItemClientData :: TreeCtrl a -> TreeItem -> IO () -> b -> IO ()
Attach a haskell value to tree item data. The IO action
 executed when the object is deleted.
evtHandlerWithClientData :: EvtHandler a -> b -> ((b -> IO ()) -> IO b -> IO c) -> IO c
Use attached haskell data locally in a type-safe way.
evtHandlerSetClientData :: EvtHandler a -> IO () -> b -> IO ()
Attach a haskell value to an object derived from EvtHandler. The IO action
 executed when the object is deleted.
objectWithClientData :: WxObject a -> b -> ((b -> IO ()) -> IO b -> IO c) -> IO c
Use attached haskell data locally. This makes it type-safe.
objectSetClientData :: WxObject a -> IO () -> b -> IO ()
Attach haskell value to an arbitrary object. The IO action is executed
 when the object is deleted. Note: evtHandlerSetClientData is preferred when possible.
Input sink
inputSinkEventLastString :: InputSinkEvent a -> IO String
Read the input from an InputSinkEvent.
Keys
type KeyCode = Int
A low-level virtual key code.
modifiersToAccelFlags :: Modifiers -> Int
Tranform modifiers into an accelerator modifiers code.
keyCodeToKey :: KeyCode -> Key
A virtual key code to a key.
keyToKeyCode :: Key -> KeyCode
From a key to a virtual key code.
Events
windowOnEvent :: Window a -> [EventId] -> handler -> (Event () -> IO ()) -> IO ()
Set a generic event handler on a certain window.
windowOnEventEx :: Window a -> [EventId] -> handler -> (Bool -> IO ()) -> (Event () -> IO ()) -> IO ()
Set a generic event handler on a certain window. Takes also a computation
 that is run when the event handler is destroyed -- the argument is True if the
 owner is deleted, and False if the event handler is disconnected for example.
Generic
type OnEvent = (Bool -> IO ()) -> (Event () -> IO ()) -> IO ()
Type synonym to make the type signatures shorter for the documentation :-)
evtHandlerOnEvent :: EvtHandler a -> Id -> Id -> [EventId] -> handler -> OnEvent
Sets a generic event handler, just as evtHandlerOnEventConnect but first
 disconnects any event handlers for the same kind of events.
evtHandlerOnEventConnect :: EvtHandler a -> Id -> Id -> [EventId] -> state -> OnEvent
Sets a generic event handler on an EvtHandler object. The call
 (evtHandlerOnEventConnect firstId lastId eventIds state destroy handler object) sets an event
 handler handler on object. The eventhandler gets called whenever an event
 happens that is in the list eventIds on an object with an Id between firstId
 and lastId (use -1 for any object). The state is any kind of haskell data
 that is attached to this handler. It can be retrieved via unsafeGetHandlerState.
 Normally, the state is the event handler itself. This allows the current event
 handler to be retrieved via calls to buttonGetOnCommand for example. The destroy
 action is called when the event handler is destroyed. Its argument is True when the
 owner is deleted, and False if the event handler is just disconnected.
Unsafe
unsafeTreeCtrlGetItemClientData :: TreeCtrl a -> TreeItem -> IO (Maybe b)
Retrieve an attached haskell value to a tree item, previously attached with treeCtrlSetItemClientData.
unsafeEvtHandlerGetClientData :: EvtHandler a -> IO (Maybe b)
Retrieve an attached haskell value, previously attached with evtHandlerSetClientData.
unsafeObjectGetClientData :: WxObject a -> IO (Maybe b)
Retrieve an attached haskell value.
unsafeGetHandlerState :: EvtHandler a -> Id -> EventId -> b -> IO b
Retrievs the state associated with a certain event handler. If
 no event handler is defined for this kind of event or Id, the
 default value is returned.
unsafeWindowGetHandlerState :: Window a -> EventId -> b -> IO b
Retrieve the event handler state for a certain event on a window.