wx-0.10.1: wxHaskell is a portable and native GUI library for Haskell.Source codeContentsIndex
Graphics.UI.WX.Controls
Contents
Classes
Containers
Controls
Button
Text entry
CheckBox
Choice
ComboBox
ListBox
RadioBox
Spin Control
Slider
Gauge
Tree control
List control
Static text
SplitterWindow
ImageList
MediaCtrl
StyledTextCtrl
Description
Synopsis
data Align
= AlignLeft
| AlignRight
| AlignCentre
class Aligned w where
alignment :: CreateAttr w Align
alignment :: Aligned w => CreateAttr w Align
data Wrap
= WrapNone
| WrapLine
| WrapWord
class Wrapped w where
wrap :: CreateAttr w Wrap
wrap :: Wrapped w => CreateAttr w Wrap
class Sorted w where
sorted :: CreateAttr w Bool
sorted :: Sorted w => CreateAttr w Bool
panel :: Window a -> [Prop (Panel ())] -> IO (Panel ())
panelEx :: Window a -> Style -> [Prop (Panel ())] -> IO (Panel ())
defaultButton :: Attr (Panel p) (Button ())
notebook :: Window a -> [Prop (Notebook ())] -> IO (Notebook ())
focusOn :: Window a -> IO ()
button :: Window a -> [Prop (Button ())] -> IO (Button ())
buttonEx :: Window a -> Style -> [Prop (Button ())] -> IO (Button ())
smallButton :: Window a -> [Prop (Button ())] -> IO (Button ())
bitmapButton :: Window a -> [Prop (BitmapButton ())] -> IO (BitmapButton ())
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 ())
processEnter :: Styled w => Attr w Bool
processTab :: Styled w => Attr w Bool
checkBox :: Window a -> [Prop (CheckBox ())] -> IO (CheckBox ())
choice :: Window a -> [Prop (Choice ())] -> IO (Choice ())
choiceEx :: Window a -> Style -> [Prop (Choice ())] -> IO (Choice ())
comboBox :: Window a -> [Prop (ComboBox ())] -> IO (ComboBox ())
comboBoxEx :: Window a -> Style -> [Prop (ComboBox ())] -> IO (ComboBox ())
type SingleListBox a = ListBox (CSingleListBox a)
type MultiListBox a = ListBox (CMultiListBox a)
singleListBox :: Window a -> [Prop (SingleListBox ())] -> IO (SingleListBox ())
multiListBox :: Window a -> [Prop (MultiListBox ())] -> IO (MultiListBox ())
radioBox :: Window a -> Orientation -> [String] -> [Prop (RadioBox ())] -> IO (RadioBox ())
spinCtrl :: Window a -> Int -> Int -> [Prop (SpinCtrl ())] -> IO (SpinCtrl ())
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 ())
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 ())
treeCtrl :: Window a -> [Prop (TreeCtrl ())] -> IO (TreeCtrl ())
treeCtrlEx :: Window a -> Style -> [Prop (TreeCtrl ())] -> IO (TreeCtrl ())
treeEvent :: Event (TreeCtrl a) (EventTree -> IO ())
listCtrl :: Window a -> [Prop (ListCtrl ())] -> IO (ListCtrl ())
listCtrlEx :: Window a -> Style -> [Prop (ListCtrl ())] -> IO (ListCtrl ())
listEvent :: Event (ListCtrl a) (EventList -> IO ())
columns :: Attr (ListCtrl a) [(String, Align, Int)]
staticText :: Window a -> [Prop (StaticText ())] -> IO (StaticText ())
splitterWindow :: Window a -> [Prop (SplitterWindow ())] -> IO (SplitterWindow ())
imageList :: Size -> IO (ImageList ())
imageListFromFiles :: Size -> [FilePath] -> IO (ImageList ())
data MediaCtrlBackend
= DirectShow
| MediaControlInterface
| WindowsMediaPlayer10
| QuickTime
| GStreamer
| DefaultBackend
mediaCtrl :: Window a -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ())
mediaCtrlWithBackend :: Window a -> MediaCtrlBackend -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ())
mediaCtrlEx :: Window a -> Style -> MediaCtrlBackend -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ())
stcEvent :: Event (StyledTextCtrl ()) (EventSTC -> IO ())
styledTextCtrl :: Window a -> [Prop (StyledTextCtrl ())] -> IO (StyledTextCtrl ())
styledTextCtrlEx :: Window a -> Style -> [Prop (StyledTextCtrl ())] -> IO (StyledTextCtrl ())
Classes
data Align Source
Alignment.
Constructors
AlignLeft
AlignRight
AlignCentre
show/hide Instances
class Aligned w whereSource
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.
Methods
alignment :: CreateAttr w AlignSource
Set the alignment of the content. Due to wxWidgets constrictions, this property has to be set at creation time.
alignment :: Aligned w => CreateAttr w AlignSource
Set the alignment of the content. Due to wxWidgets constrictions, this property has to be set at creation time.
data Wrap Source
Wrap mode.
Constructors
WrapNoneNo wrapping (and show a horizontal scrollbar).
WrapLineWrap lines that are too long at any position.
WrapWordWrap lines that are too long at word boundaries.
show/hide Instances
class Wrapped w whereSource
Widgets that have wrappable content.
Methods
wrap :: CreateAttr w WrapSource
Set the wrap mode of a widget.
wrap :: Wrapped w => CreateAttr w WrapSource
Set the wrap mode of a widget.
class Sorted w whereSource
Widgets that have sorted contents.
Methods
sorted :: CreateAttr w BoolSource
Is the content of the widget sorted?
sorted :: Sorted w => CreateAttr w BoolSource
Is the content of the widget sorted?
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).

panelEx :: Window a -> Style -> [Prop (Panel ())] -> IO (Panel ())Source

Create a Panel with a specific style.

defaultButton :: Attr (Panel p) (Button ())Source
notebook :: Window a -> [Prop (Notebook ())] -> IO (Notebook ())Source

Create a Notebook. Layout is managed with the tabs combinator.

focusOn :: Window a -> IO ()Source
Set the initial focus on this control.
Controls
Button
button :: Window a -> [Prop (Button ())] -> IO (Button ())Source

Create a standard push button.

buttonEx :: Window a -> Style -> [Prop (Button ())] -> IO (Button ())Source

Create a standard push button with the given flags.

smallButton :: Window a -> [Prop (Button ())] -> IO (Button ())Source

Create a minimially sized push button.

bitmapButton :: Window a -> [Prop (BitmapButton ())] -> IO (BitmapButton ())Source

Create a bitmap button. Use the image attribute to set the bitmap.

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) ).

textEntry :: 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) ).

textCtrl :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ())Source

Create a multi-line text control. Note: the wrap and alignment have to be set at creation time or the default to WrapNone and AlignLeft respectively.

textCtrlRich :: Window a -> [Prop (TextCtrl ())] -> IO (TextCtrl ())Source

Create a multi-line text rich-text control with a certain wrap mode Enables font and color settings on windows, while being equal to textCtrl on other platforms. Note: the wrap and alignment have to be set at creation time or the default to WrapNone and AlignLeft respectively.

textCtrlEx :: Window a -> Style -> [Prop (TextCtrl ())] -> IO (TextCtrl ())Source

Create a generic text control given a certain style.

processEnter :: Styled w => Attr w BoolSource
Process enter key events, used in a comboBox or textCtrl and catched using a on command handler. (otherwise pressing Enter is either processed internally by the control or used for navigation between dialog controls).
processTab :: Styled w => Attr w BoolSource
Process tab key events, used in a comboBox or textCtrl. (otherwise pressing Tab is either processed internally by the control or used for navigation between dialog controls).
CheckBox
checkBox :: Window a -> [Prop (CheckBox ())] -> IO (CheckBox ())Source

Create a new checkbox.

Choice
choice :: Window a -> [Prop (Choice ())] -> IO (Choice ())Source

Create a choice item to select a one of a list of strings.

choiceEx :: Window a -> Style -> [Prop (Choice ())] -> IO (Choice ())Source

Create a choice item, given a set of style flags, to select a one of a list of strings

ComboBox
comboBox :: Window a -> [Prop (ComboBox ())] -> IO (ComboBox ())Source

Create a new combo box.

A command event is triggered when the enter key is pressed and when processEnter has been set to True.

comboBoxEx :: Window a -> Style -> [Prop (ComboBox ())] -> IO (ComboBox ())Source

Create a new combo box with a given set of flags.

A command event is triggered when the enter key is pressed and when processEnter has been set to True.

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

Create a single selection list box.

multiListBox :: Window a -> [Prop (MultiListBox ())] -> IO (MultiListBox ())Source
RadioBox
radioBox :: Window a -> Orientation -> [String] -> [Prop (RadioBox ())] -> IO (RadioBox ())Source

Create a new radio button group with an initial orientation and a list of labels. Use selection to get the currently selected item.

Spin Control
spinCtrl :: Window a -> Int -> Int -> [Prop (SpinCtrl ())] -> IO (SpinCtrl ())Source

Create a spin control: a text field with up/down buttons. The value (selection) is always between a specified minimum and maximum.

Slider
hslider :: Window a -> Bool -> Int -> Int -> [Prop (Slider ())] -> IO (Slider ())Source

Create a horizontal slider with a specified minimum and maximum. Set the Bool argument to True to show labels (minimumn, maximum, and current value). The selection attribute gives the current value.

vslider :: Window a -> Bool -> Int -> Int -> [Prop (Slider ())] -> IO (Slider ())Source

Create a vertical slider with a specified minimum and maximum. Set the Bool argument to True to show labels (minimumn, maximum, and current value). The selection attribute gives the current value.

sliderEx :: Window a -> Int -> Int -> Style -> [Prop (Slider ())] -> IO (Slider ())Source

Create a slider with a specified minimum and maximum. The selection attribute gives the current value.

Gauge
hgauge :: Window a -> Int -> [Prop (Gauge ())] -> IO (Gauge ())Source

Create a horizontal gauge with a specified integer range (max value). The selection attribute determines the position of the gauge.

vgauge :: Window a -> Int -> [Prop (Gauge ())] -> IO (Gauge ())Source

Create a vertical gauge with a specified integer range (max value). The selection attribute determines the position of the gauge.

gaugeEx :: Window a -> Int -> Style -> [Prop (Gauge ())] -> IO (Gauge ())Source

Create a gauge control. The selection attribute determines the position of the gauge.

Tree control
treeCtrl :: Window a -> [Prop (TreeCtrl ())] -> IO (TreeCtrl ())Source

Create a single-selection tree control with buttons (i.e. + and - signs).

treeCtrlEx :: Window a -> Style -> [Prop (TreeCtrl ())] -> IO (TreeCtrl ())Source

Create a tree control.

treeEvent :: Event (TreeCtrl a) (EventTree -> IO ())Source
Tree control events.
List control
listCtrl :: Window a -> [Prop (ListCtrl ())] -> IO (ListCtrl ())Source

Create a report-style list control.

listCtrlEx :: Window a -> Style -> [Prop (ListCtrl ())] -> IO (ListCtrl ())Source

Create a list control.

listEvent :: Event (ListCtrl a) (EventList -> IO ())Source
List control events.
columns :: Attr (ListCtrl a) [(String, Align, Int)]Source
The columns attribute controls the columns in a report-view list control.
Static text
staticText :: Window a -> [Prop (StaticText ())] -> IO (StaticText ())Source
Create static text label, see also label.
SplitterWindow
splitterWindow :: Window a -> [Prop (SplitterWindow ())] -> IO (SplitterWindow ())Source

Create a splitter window.

ImageList
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 back-end for your MediaCtrl. If you want to know more about back-end, you must see wxWidgets' Document. http://www.wxwidgets.org/manuals/stable/wx_wxmediactrl.html#choosingbackendwxmediactrl
Constructors
DirectShowUse ActiveMovie/DirectShow. Default back-end on Windows.
MediaControlInterfaceUse Media Command Interface. Windows Only.
WindowsMediaPlayer10Use Windows Media Player 10. Windows Only. Require to use wxWidgets 2.8.x.
QuickTimeUse QuickTime. Mac Only.
GStreamerUse GStreamer. Unix Only. Require GStreamer and GStreamer Support.
DefaultBackendUse default back-end on your platform.
show/hide Instances
mediaCtrl :: Window a -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ())Source
mediaCtrlWithBackend :: Window a -> MediaCtrlBackend -> [Prop (MediaCtrl ())] -> IO (MediaCtrl ())Source

Create MediaCtrl with choosing back-end. This is useful to select back-end 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
StyledTextCtrl
stcEvent :: Event (StyledTextCtrl ()) (EventSTC -> IO ())Source
styledTextCtrl :: Window a -> [Prop (StyledTextCtrl ())] -> IO (StyledTextCtrl ())Source
styledTextCtrlEx :: Window a -> Style -> [Prop (StyledTextCtrl ())] -> IO (StyledTextCtrl ())Source
Produced by Haddock version 2.1.0