Copyright | (c) Daan Leijen 2003 (c) Shelarcy (shelarcy@gmail.com) 2006 |
---|---|
License | wxWindows |
Maintainer | wxhaskell-devel@lists.sourceforge.net |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Defines common GUI controls.
- data Align
- class Aligned w where
- alignment :: Aligned w => CreateAttr w Align
- data Wrap
- class Wrapped w where
- wrap :: Wrapped w => CreateAttr w Wrap
- class Sorted w where
- sorted :: Sorted w => CreateAttr w Bool
- calendarCtrl :: Window a -> [Prop (CalendarCtrl ())] -> IO (CalendarCtrl ())
- date :: (Typeable a, IsDate a) => Attr (CalendarCtrl w) a
- class IsDate a where
- type Panel a = Window (CPanel a)
- panel :: Window a -> [Prop (Panel ())] -> IO (Panel ())
- panelEx :: Window a -> Style -> [Prop (Panel ())] -> IO (Panel ())
- type Notebook a = Control (CNotebook a)
- notebook :: Window a -> [Prop (Notebook ())] -> IO (Notebook ())
- focusOn :: Window a -> IO ()
- type Button a = Control (CButton a)
- button :: Window a -> [Prop (Button ())] -> IO (Button ())
- buttonEx :: Window a -> Style -> [Prop (Button ())] -> IO (Button ())
- smallButton :: Window a -> [Prop (Button ())] -> IO (Button ())
- buttonRes :: Window a -> String -> [Prop (Button ())] -> IO (Button ())
- type BitmapButton a = Button (CBitmapButton a)
- bitmapButton :: Window a -> [Prop (BitmapButton ())] -> IO (BitmapButton ())
- bitmapButtonRes :: Window a -> String -> [Prop (BitmapButton ())] -> IO (BitmapButton ())
- type TextCtrl a = Control (CTextCtrl a)
- entry :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ())
- textEntry :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ())
- textCtrl :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ())
- textCtrlRich :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ())
- textCtrlEx :: Window a -> Style -> [Prop (TextCtrl ())] -> IO (TextCtrl ())
- textCtrlRes :: Window a -> String -> [Prop (TextCtrl ())] -> IO (TextCtrl ())
- processEnter :: Styled w => Attr w Bool
- processTab :: Styled w => Attr w Bool
- type CheckBox a = Control (CCheckBox a)
- checkBox :: Window a -> [Prop (CheckBox ())] -> IO (CheckBox ())
- checkBoxRes :: Window a -> String -> [Prop (CheckBox ())] -> IO (CheckBox ())
- type Choice a = Control (CChoice a)
- choice :: Window a -> [Prop (Choice ())] -> IO (Choice ())
- choiceEx :: Window a -> Style -> [Prop (Choice ())] -> IO (Choice ())
- choiceRes :: Window a -> String -> [Prop (Choice ())] -> IO (Choice ())
- type ComboBox a = Choice (CComboBox a)
- comboBox :: Window a -> [Prop (ComboBox ())] -> IO (ComboBox ())
- comboBoxEx :: Window a -> Style -> [Prop (ComboBox ())] -> IO (ComboBox ())
- comboBoxRes :: Window a -> String -> [Prop (ComboBox ())] -> IO (ComboBox ())
- type ListBox a = Control (CListBox a)
- type SingleListBox a = ListBox (CSingleListBox a)
- type MultiListBox a = ListBox (CMultiListBox a)
- singleListBox :: Window a -> [Prop (SingleListBox ())] -> IO (SingleListBox ())
- singleListBoxRes :: Window a -> String -> [Prop (SingleListBox ())] -> IO (SingleListBox ())
- multiListBox :: Window a -> [Prop (MultiListBox ())] -> IO (MultiListBox ())
- multiListBoxRes :: Window a -> String -> [Prop (MultiListBox ())] -> IO (MultiListBox ())
- data ListBoxView b a = ListBoxView {
- listBoxViewCtrl :: ListBox b
- listBoxViewItems :: Var [a]
- listBoxViewToRow :: a -> String
- singleListBoxView :: Window b -> [Prop (SingleListBox ())] -> (a -> String) -> IO (ListBoxView (CSingleListBox ()) a)
- multiListBoxView :: Window b -> [Prop (MultiListBox ())] -> (a -> String) -> IO (ListBoxView (CMultiListBox ()) a)
- listBoxViewAddItem :: ListBoxView b a -> a -> IO ()
- listBoxViewGetItems :: ListBoxView b a -> IO [a]
- listBoxViewSetItems :: ListBoxView b a -> [a] -> IO ()
- singleListBoxViewGetSelection :: ListBoxView (CSingleListBox ()) a -> IO (Maybe a)
- multiListBoxViewGetSelections :: ListBoxView (CMultiListBox ()) a -> IO [a]
- type RadioBox a = Control (CRadioBox a)
- radioBox :: Window a -> Orientation -> [String] -> [Prop (RadioBox ())] -> IO (RadioBox ())
- radioBoxRes :: Window a -> String -> [Prop (RadioBox ())] -> IO (RadioBox ())
- type SpinCtrl a = Control (CSpinCtrl a)
- spinCtrl :: Window a -> Int -> Int -> [Prop (SpinCtrl ())] -> IO (SpinCtrl ())
- spinCtrlRes :: Window a -> String -> [Prop (SpinCtrl ())] -> IO (SpinCtrl ())
- type Slider a = Control (CSlider a)
- hslider :: Window a -> Bool -> Int -> Int -> [Prop (Slider ())] -> IO (Slider ())
- vslider :: Window a -> Bool -> Int -> Int -> [Prop (Slider ())] -> IO (Slider ())
- sliderEx :: Window a -> Int -> Int -> Style -> [Prop (Slider ())] -> IO (Slider ())
- sliderRes :: Window a -> String -> [Prop (Slider ())] -> IO (Slider ())
- type Gauge a = Control (CGauge a)
- hgauge :: Window a -> Int -> [Prop (Gauge ())] -> IO (Gauge ())
- vgauge :: Window a -> Int -> [Prop (Gauge ())] -> IO (Gauge ())
- gaugeEx :: Window a -> Int -> Style -> [Prop (Gauge ())] -> IO (Gauge ())
- gaugeRes :: Window a -> String -> [Prop (Gauge ())] -> IO (Gauge ())
- type ToggleButton a = Control (CToggleButton a)
- type BitmapToggleButton a = ToggleButton (CBitmapToggleButton a)
- toggleButton :: Window a -> [Prop (ToggleButton ())] -> IO (ToggleButton ())
- bitmapToggleButton :: Window a -> [Prop (BitmapToggleButton ())] -> IO (BitmapToggleButton ())
- type TreeCtrl a = Control (CTreeCtrl a)
- treeCtrl :: Window a -> [Prop (TreeCtrl ())] -> IO (TreeCtrl ())
- treeCtrlEx :: Window a -> Style -> [Prop (TreeCtrl ())] -> IO (TreeCtrl ())
- treeEvent :: Event (TreeCtrl a) (EventTree -> IO ())
- treeCtrlRes :: Window a -> String -> [Prop (TreeCtrl ())] -> IO (TreeCtrl ())
- type ListCtrl a = Control (CListCtrl a)
- listCtrl :: Window a -> [Prop (ListCtrl ())] -> IO (ListCtrl ())
- listCtrlEx :: Window a -> Style -> [Prop (ListCtrl ())] -> IO (ListCtrl ())
- listCtrlRes :: Window a -> String -> [Prop (ListCtrl ())] -> IO (ListCtrl ())
- listCtrlSetColumnWidths :: ListCtrl () -> Int -> IO ()
- listEvent :: Event (ListCtrl a) (EventList -> IO ())
- columns :: Attr (ListCtrl a) [(String, Align, Int)]
- data ListView a = ListView {
- listViewCtrl :: ListCtrl ()
- listViewItems :: Var [a]
- listViewToRow :: a -> [String]
- listViewLayout :: ListView a -> Layout
- listViewSetHandler :: ListView a -> (EventList -> IO ()) -> IO ()
- listViewSelectHandle :: ListView a -> (Maybe a -> IO ()) -> EventList -> IO ()
- listViewSetItems :: ListView a -> [a] -> IO ()
- listViewGetItems :: ListView a -> IO [a]
- listViewAddItem :: ListView a -> a -> IO ()
- listView :: Window b -> [String] -> (a -> [String]) -> IO (ListView a)
- type StaticText a = Control (CStaticText a)
- staticText :: Window a -> [Prop (StaticText ())] -> IO (StaticText ())
- staticTextRes :: Window a -> String -> [Prop (StaticText ())] -> IO (StaticText ())
- type SplitterWindow a = Window (CSplitterWindow a)
- splitterWindow :: Window a -> [Prop (SplitterWindow ())] -> IO (SplitterWindow ())
- type ImageList a = WxObject (CImageList a)
- imageList :: Size -> IO (ImageList ())
- imageListFromFiles :: Size -> [FilePath] -> IO (ImageList ())
- data MediaCtrlBackend
- type MediaCtrl a = Window (CMediaCtrl a)
- mediaCtrl :: Window a -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ())
- mediaCtrlWithBackend :: Window a -> MediaCtrlBackend -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ())
- mediaCtrlEx :: Window a -> Style -> MediaCtrlBackend -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ())
- type Wizard a = Dialog (CWizard a)
- wizard :: Window a -> [Prop (Wizard ())] -> IO (Wizard ())
- wizardEx :: Window a -> Style -> [Prop (Wizard ())] -> IO (Wizard ())
- wizardPageSimple :: Wizard a -> [Prop (WizardPageSimple ())] -> IO (WizardPageSimple ())
- runWizard :: Wizard a -> WizardPage b -> IO Bool
- next :: WriteAttr (WizardPageSimple a) (Maybe (WizardPageSimple b))
- prev :: WriteAttr (WizardPageSimple a) (Maybe (WizardPageSimple b))
- chain :: [WizardPageSimple a] -> IO ()
- wizardPageSize :: Attr (Wizard a) Size
- wizardEvent :: Event (Wizard a) (EventWizard -> IO ())
- wizardCurrentPage :: ReadAttr (Wizard a) (Maybe (WizardPage ()))
- type StyledTextCtrl a = Control (CStyledTextCtrl a)
- stcEvent :: Event (StyledTextCtrl ()) (EventSTC -> IO ())
- styledTextCtrl :: Window a -> [Prop (StyledTextCtrl ())] -> IO (StyledTextCtrl ())
- styledTextCtrlEx :: Window a -> Style -> [Prop (StyledTextCtrl ())] -> IO (StyledTextCtrl ())
- type PropertyGrid a = Control (CPropertyGrid a)
- propertyGrid :: Window a -> [Prop (PropertyGrid ())] -> IO (PropertyGrid ())
- propertyGridEvent :: Event (PropertyGrid a) (EventPropertyGrid -> IO ())
Classes
Alignment.
class Aligned w where Source #
Widgets that can have aligned content. Note: this property is not used to set the alignment of a widget itself -- See Graphics.UI.WXCore.Layout for more information about layout.
alignment :: CreateAttr w Align Source #
Set the alignment of the content. Due to wxWidgets constrictions, this property has to be set at creation time.
alignment :: Aligned w => CreateAttr w Align Source #
Set the alignment of the content. Due to wxWidgets constrictions, this property has to be set at creation time.
Wrap mode.
class Wrapped w where Source #
Widgets that have wrappable content.
wrap :: CreateAttr w Wrap Source #
Set the wrap mode of a widget.
Widgets that have sorted contents.
sorted :: CreateAttr w Bool Source #
Is the content of the widget sorted?
Calendar Ctrl
calendarCtrl :: Window a -> [Prop (CalendarCtrl ())] -> IO (CalendarCtrl ()) Source #
Containers
panel :: Window a -> [Prop (Panel ())] -> IO (Panel ()) Source #
Create a Panel
, a window that is normally used as a container for
controls. It has a standard background and maintains standard keyboard
navigation (ie. Tab moves through the controls).
Note: the defaultButton
attribute is removed. Set defaultButton
to parent
Frame
or Dialog
instead of this control now. This is an incompatible
change to support wxWidgets 2.8.x.
panelEx :: Window a -> Style -> [Prop (Panel ())] -> IO (Panel ()) Source #
Create a Panel
with a specific style.
Note: the defaultButton
attribute is removed. Set defaultButton
to parent
Frame
or Dialog
instead of this control now. This is an incompatible
change to support wxWidgets 2.8.x.
Controls
Button
type BitmapButton a = Button (CBitmapButton a) #
Pointer to an object of type BitmapButton
, derived from Button
.
bitmapButton :: Window a -> [Prop (BitmapButton ())] -> IO (BitmapButton ()) Source #
bitmapButtonRes :: Window a -> String -> [Prop (BitmapButton ())] -> IO (BitmapButton ()) Source #
Text entry
entry :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ()) Source #
Create a single-line text entry control. Note: alignment
has to
be set at creation time (or the entry has default alignment (=left) ).
This is an alias for textEntry
textCtrl :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ()) Source #
textCtrlRich :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ()) Source #
CheckBox
Choice
choiceRes :: Window a -> String -> [Prop (Choice ())] -> IO (Choice ()) Source #
Complete the construction of a choice instance which has been loaded from a resource file.
ComboBox
comboBoxEx :: Window a -> Style -> [Prop (ComboBox ())] -> IO (ComboBox ()) Source #
Create a new combo box with a given set of flags.
- Instances:
Selecting
,Commanding
,Updating
,Selection
,Items
--Textual
,Literate
,Dimensions
,Colored
,Visible
,Child
,Able
,Tipped
,Identity
,Styled
,Reactive
,Paint
.
A command
event is triggered when the enter
key is pressed and when
processEnter
has been set to True
.
comboBoxRes :: Window a -> String -> [Prop (ComboBox ())] -> IO (ComboBox ()) Source #
Complete the construction of a combo box instance which has been loaded from a resource file.
ListBox
type SingleListBox a = ListBox (CSingleListBox a) Source #
Pointer to single selection list boxes, deriving from ListBox
.
type MultiListBox a = ListBox (CMultiListBox a) Source #
Pointer to multiple selection list boxes, deriving from ListBox
.
singleListBox :: Window a -> [Prop (SingleListBox ())] -> IO (SingleListBox ()) Source #
singleListBoxRes :: Window a -> String -> [Prop (SingleListBox ())] -> IO (SingleListBox ()) Source #
Complete the construction of a single list box instance which has been loaded from a resource file.
multiListBox :: Window a -> [Prop (MultiListBox ())] -> IO (MultiListBox ()) Source #
multiListBoxRes :: Window a -> String -> [Prop (MultiListBox ())] -> IO (MultiListBox ()) Source #
Complete the construction of a single list box instance which has been loaded from a resource file.
data ListBoxView b a Source #
A small wrapper over WX's ListCtrl, allowing us to keep the data we're representing as well as its string form (shown to the user as rows).
ListBoxView | |
|
singleListBoxView :: Window b -> [Prop (SingleListBox ())] -> (a -> String) -> IO (ListBoxView (CSingleListBox ()) a) Source #
multiListBoxView :: Window b -> [Prop (MultiListBox ())] -> (a -> String) -> IO (ListBoxView (CMultiListBox ()) a) Source #
listBoxViewAddItem :: ListBoxView b a -> a -> IO () Source #
listBoxViewGetItems :: ListBoxView b a -> IO [a] Source #
listBoxViewSetItems :: ListBoxView b a -> [a] -> IO () Source #
singleListBoxViewGetSelection :: ListBoxView (CSingleListBox ()) a -> IO (Maybe a) Source #
multiListBoxViewGetSelections :: ListBoxView (CMultiListBox ()) a -> IO [a] Source #
RadioBox
radioBox :: Window a -> Orientation -> [String] -> [Prop (RadioBox ())] -> IO (RadioBox ()) Source #
radioBoxRes :: Window a -> String -> [Prop (RadioBox ())] -> IO (RadioBox ()) Source #
Complete the construction of a radio box instance which has been loaded from a resource file.
Spin Control
spinCtrlRes :: Window a -> String -> [Prop (SpinCtrl ())] -> IO (SpinCtrl ()) Source #
Complete the construction of a spin control instance which has been loaded from a resource file.
Slider
hslider :: Window a -> Bool -> Int -> Int -> [Prop (Slider ())] -> IO (Slider ()) Source #
vslider :: Window a -> Bool -> Int -> Int -> [Prop (Slider ())] -> IO (Slider ()) Source #
sliderRes :: Window a -> String -> [Prop (Slider ())] -> IO (Slider ()) Source #
Complete the construction of a slider instance which has been loaded from a resource file.
Gauge
gaugeRes :: Window a -> String -> [Prop (Gauge ())] -> IO (Gauge ()) Source #
Complete the construction of a gauge instance which has been loaded from a resource file.
ToggleButton
type ToggleButton a = Control (CToggleButton a) #
Pointer to an object of type ToggleButton
, derived from Control
.
type BitmapToggleButton a = ToggleButton (CBitmapToggleButton a) #
Pointer to an object of type BitmapToggleButton
, derived from ToggleButton
.
toggleButton :: Window a -> [Prop (ToggleButton ())] -> IO (ToggleButton ()) Source #
bitmapToggleButton :: Window a -> [Prop (BitmapToggleButton ())] -> IO (BitmapToggleButton ()) Source #
Tree control
treeCtrlRes :: Window a -> String -> [Prop (TreeCtrl ())] -> IO (TreeCtrl ()) Source #
Complete the construction of a tree control instance which has been loaded from a resource file.
List control
listCtrlRes :: Window a -> String -> [Prop (ListCtrl ())] -> IO (ListCtrl ()) Source #
Complete the construction of a list control instance which has been loaded from a resource file.
columns :: Attr (ListCtrl a) [(String, Align, Int)] Source #
The columns
attribute controls the columns in a report-view list control.
A small wrapper over WX's ListCtrl
, allowing us to keep the data
we're representing as well as its string form (shown to the user as
rows).
ListView | |
|
listViewLayout :: ListView a -> Layout Source #
listViewSetItems :: ListView a -> [a] -> IO () Source #
listViewGetItems :: ListView a -> IO [a] Source #
listViewAddItem :: ListView a -> a -> IO () Source #
Static text
type StaticText a = Control (CStaticText a) #
Pointer to an object of type StaticText
, derived from Control
.
staticText :: Window a -> [Prop (StaticText ())] -> IO (StaticText ()) Source #
Create static text label, see also label
.
staticTextRes :: Window a -> String -> [Prop (StaticText ())] -> IO (StaticText ()) Source #
Complete the construction of a static text label instance which has been loaded from a resource file.
SplitterWindow
type SplitterWindow a = Window (CSplitterWindow a) #
Pointer to an object of type SplitterWindow
, derived from Window
.
splitterWindow :: Window a -> [Prop (SplitterWindow ())] -> IO (SplitterWindow ()) Source #
ImageList
type ImageList a = WxObject (CImageList a) #
imageList :: Size -> IO (ImageList ()) Source #
Create an empty image list that will contain images of the desired size.
imageListFromFiles :: Size -> [FilePath] -> IO (ImageList ()) Source #
Create an image list containing the images in the supplied file name list that will be scaled towards the desired size.
MediaCtrl
data MediaCtrlBackend Source #
Optional backend for your MediaCtrl. If you want to know more about backend, you must see wxWidgets' document: http://docs.wxwidgets.org/trunk/classwx_media_ctrl.html#mediactrl_choosing_backend
DirectShow | Use ActiveMovie/DirectShow. Default backend on Windows. |
MediaControlInterface | Use Media Command Interface. Windows Only. |
WindowsMediaPlayer10 | Use Windows Media Player 10. Windows Only. Require to use wxWidgets 2.8.x. |
QuickTime | Use QuickTime. Mac Only. |
GStreamer | Use GStreamer. Unix Only. Require GStreamer and GStreamer Support. |
DefaultBackend | Use default backend on your platform. |
type MediaCtrl a = Window (CMediaCtrl a) #
mediaCtrlWithBackend :: Window a -> MediaCtrlBackend -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ()) Source #
Create MediaCtrl with choosing backend. This is useful to select backend on Windows. But if you don't want to cause any effect to other platforms, you must use wxToolkit or #ifdef macro to choose correct function for platforms. For example,
import Graphics.UI.WXCore.Defines ... m <- case wxToolkit of WxMSW -> mediaCtrlWithBackend f MediaControlInterface [] _ -> mediaCtrl f []
or
#ifdef mingw32_HOST_OS || mingw32_TARGET_OS m <- mediaCtrlWithBackend f MediaControlInterface [] #else m <- mediaCtrl f [] #endif
mediaCtrlEx :: Window a -> Style -> MediaCtrlBackend -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ()) Source #
Wizard
wizardPageSimple :: Wizard a -> [Prop (WizardPageSimple ())] -> IO (WizardPageSimple ()) Source #
Create an empty simple wizard page.
runWizard :: Wizard a -> WizardPage b -> IO Bool Source #
Run the wizard.
IMPORTANT: windowDestroy
must be called on the wizard when it is no longer used. After
windowDestroy
has been called, the wizard or any of its children must not be accessed anymore.
next :: WriteAttr (WizardPageSimple a) (Maybe (WizardPageSimple b)) Source #
prev :: WriteAttr (WizardPageSimple a) (Maybe (WizardPageSimple b)) Source #
chain :: [WizardPageSimple a] -> IO () Source #
Chain together all given wizard pages.
wizardEvent :: Event (Wizard a) (EventWizard -> IO ()) Source #
wizardCurrentPage :: ReadAttr (Wizard a) (Maybe (WizardPage ())) Source #
StyledTextCtrl
type StyledTextCtrl a = Control (CStyledTextCtrl a) #
Pointer to an object of type StyledTextCtrl
, derived from Control
.
styledTextCtrl :: Window a -> [Prop (StyledTextCtrl ())] -> IO (StyledTextCtrl ()) Source #
styledTextCtrlEx :: Window a -> Style -> [Prop (StyledTextCtrl ())] -> IO (StyledTextCtrl ()) Source #
PropertyGrid
type PropertyGrid a = Control (CPropertyGrid a) #
Pointer to an object of type PropertyGrid
, derived from Control
.
propertyGrid :: Window a -> [Prop (PropertyGrid ())] -> IO (PropertyGrid ()) Source #
propertyGridEvent :: Event (PropertyGrid a) (EventPropertyGrid -> IO ()) Source #
PropertyGrid control events.
Orphan instances
Form (Panel a) Source # | |
Selection (Slider a) Source # | |
Selection (Gauge a) Source # | |
Selection (SpinCtrl a) Source # | |
Selection (RadioBox a) Source # | |
Selection (Choice ()) Source # | |
Selection (ComboBox a) Source # | |
Checkable (ToggleButton a) Source # | |
Checkable (CheckBox a) Source # | |
Pictured (BitmapToggleButton a) Source # | |
Pictured (BitmapButton a) Source # | |
Updating (TextCtrl a) Source # | |
Updating (ComboBox a) Source # | |
Commanding (Slider a) Source # | |
Commanding (ToggleButton a) Source # | |
Commanding (TextCtrl a) Source # | |
Commanding (Button a) Source # | |
Commanding (ComboBox a) Source # | |
Commanding (CheckBox a) Source # | |
Selecting (SpinCtrl a) Source # | |
Selecting (RadioBox a) Source # | |
Selecting (ListBox a) Source # | |
Selecting (Choice ()) Source # | |
Selecting (ComboBox a) Source # | |
Media (MediaCtrl a) Source # | |
Items (RadioBox a) String Source # | |
Items (ListBox a) String Source # | |
Items (Choice a) String Source # | |
Items (ListCtrl a) [String] Source # | |