wx-0.12.1.6: wxHaskell

Portabilityportable
Stabilityprovisional
Maintainerwxhaskell-devel@lists.sourceforge.net

Graphics.UI.WX.Controls

Contents

Description

Defines common GUI controls.

Synopsis

Classes

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.

Instances

data Wrap Source

Wrap mode.

Constructors

WrapNone

No wrapping (and show a horizontal scrollbar).

WrapLine

Wrap lines that are too long at any position.

WrapWord

Wrap lines that are too long at word boundaries.

class Wrapped w whereSource

Widgets that have wrappable content.

Methods

wrap :: CreateAttr w WrapSource

Set the wrap mode of a widget.

Instances

class Sorted w whereSource

Widgets that have sorted contents.

Methods

sorted :: CreateAttr w BoolSource

Is the content of the widget sorted?

Instances

Containers

type Panel a = Window (CPanel a)

Pointer to an object of type Panel, derived from Window.

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: defaultButton attibute 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: defaultButton attibute 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.

type Notebook a = Control (CNotebook a)

Pointer to an object of type Notebook, derived from Control.

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

type Button a = Control (CButton a)

Pointer to an object of type Button, derived from Control.

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.

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

Complete the construction of a push button instance which has been loaded from a resource file.

type BitmapButton a = Button (CBitmapButton a)

Pointer to an object of type BitmapButton, derived from Button.

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

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

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

Complete the construction of a bitmap button instance which has been loaded from a resource file.

Text entry

type TextCtrl a = Control (CTextCtrl a)

Pointer to an object of type TextCtrl, derived from Control.

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.

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

Complete the construction of a text control instance which has been loaded from a resource file.

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

type CheckBox a = Control (CCheckBox a)

Pointer to an object of type CheckBox, derived from Control.

checkBoxRes :: Window a -> String -> [Prop (CheckBox ())] -> IO (CheckBox ())Source

Complete the construction of a check box instance which has been loaded from a resource file.

Choice

type Choice a = Control (CChoice a)

Pointer to an object of type Choice, derived from Control.

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

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

type ComboBox a = Choice (CComboBox a)

Pointer to an object of type ComboBox, derived from Choice.

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.

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 ListBox a = Control (CListBox a)

Pointer to an object of type ListBox, derived from Control.

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.

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.

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.

RadioBox

type RadioBox a = Control (CRadioBox a)

Pointer to an object of type RadioBox, derived from Control.

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.

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

type SpinCtrl a = Control (CSpinCtrl a)

Pointer to an object of type SpinCtrl, derived from 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.

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

type Slider a = Control (CSlider a)

Pointer to an object of type Slider, derived from Control.

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.

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

type Gauge a = Control (CGauge a)

Pointer to an object of type Gauge, derived from Control.

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.

gaugeRes :: Window a -> String -> [Prop (Gauge ())] -> IO (Gauge ())Source

Complete the construction of a gauge instance which has been loaded from a resource file.

Tree control

type TreeCtrl a = Control (CTreeCtrl a)

Pointer to an object of type TreeCtrl, derived from 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.

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

type ListCtrl a = Control (CListCtrl a)

Pointer to an object of type ListCtrl, derived from 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.

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.

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

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.

ImageList

type ImageList a = WxObject (CImageList a)

Pointer to an object of type ImageList, derived from WxObject.

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

DirectShow

Use ActiveMovie/DirectShow. Default back-end 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 back-end on your platform.

type MediaCtrl a = Window (CMediaCtrl a)

Pointer to an object of type MediaCtrl, derived from Window.

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

StyledTextCtrl

type StyledTextCtrl a = Control (CStyledTextCtrl a)

Pointer to an object of type StyledTextCtrl, derived from Control.