xtc-1.0.1: eXtended & Typed Controls for wxHaskell.

Copyright(c) Martijn Schrage 2005
Maintainermartijn@cs.uu.nl
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Graphics.UI.XTC

Contents

Description

XTC: eXtended & Typed Controls for wxHaskell

The XTC library provides a typed interface to several wxHaskell controls.

  • radio view (typed radio box)

    • single-selection list view (typed single-selection list box)
    • muliple-selection list view (typed multiple-selection list box)
    • choice view (typed choice box)
    • value entry (typed text entry)

    XTC controls keep track of typed values and items, rather than being string based. Selections in XTC controls consist of actual values instead of indices.

Synopsis

Classes

class Labeled x where Source

The labeled class is used by mkRadioView, mkListView, mkMultiListView, and mkChoiceView for conveniently passing the function that maps an item onto its label.

Methods

toLabel :: x -> String Source

Instances

class TypedValued x w | w -> x where Source

Widgets that have a typed value. The value can be accessed via the attribute typedValue, and has type x.

Methods

typedValue :: Attr w (Maybe x) Source

Instances

class Items w String => TypedItems x w | w -> x where Source

Widgets that have a typed list of items. The item list can be accessed via the attribute typedItems, and has type [x].

Methods

typedItems :: Attr w [x] Source

Instances

class Selection w => TypedSelection x w | w -> x where Source

Widgets that have a typed selection. The selection can be accessed via the attribute typedSelection, and has type x.

Methods

typedSelection :: Attr w x Source

Instances

class Selection w => TypedMaybeSelection x w | w -> x where Source

Widgets that have a typed selection that may be empty. The selection can be accessed via the attribute typedMaybeSelection, and has type Maybe x.

class Selections w => TypedSelections x w | w -> x where Source

Widgets that have a typed list of selections. The selection list can be accessed via the attribute typedSelections, and has type [x].

Methods

typedSelections :: Attr w [x] Source

Instances

class Observable w where Source

Methods

change :: Event w (IO ()) Source

Instances

Controls

Radio view

type RadioView x b = RadioBox (CRadioView x b) Source

Pointer to a radio view, deriving from RadioBox.

mkRadioView :: Labeled x => Window a -> Orientation -> [x] -> [Prop (RadioView x ())] -> IO (RadioView x ()) Source

Create a new radio view with an initial orientation and a list of typed items. The item type (x) must be an instance of Labeled to show each item's label. Use attribute typedSelection to access the currently selected item, and typedItems to access the list of items. Note: for a radio view (or radio box) the items may not be modified dynamically.

mkRadioViewEx :: Window a -> (x -> String) -> Orientation -> [x] -> [Prop (RadioView x ())] -> IO (RadioView x ()) Source

Create a new radio view with an initial orientation and a list of typed items. A function of type (x -> String) maps items onto labels. Use attribute typedSelection to access the currently selected item, and typedItems to access the list of items. Note: for a radio view (or radio box) the items may not be modified dynamically.

Single-selection list view

type ListView a b = SingleListBox (CListView a b) Source

Pointer to a single-selection list view, deriving from SingleListBox.

mkListView :: Labeled x => Window a -> [Prop (ListView x ())] -> IO (ListView x ()) Source

Create a single-selection list view. The item type (x) must be an instance of Labeled to show each item's label. Use attribute typedMaybeSelection to access the currently selected item, and typedItems to access the list of items.

mkListViewEx :: Window a -> (x -> String) -> [Prop (ListView x ())] -> IO (ListView x ()) Source

Create a single-selection list view. A function of type (x -> String) maps items onto labels. Use attribute typedMaybeSelection to access the currently selected item, and typedItems to access the list of items.

Multiple-selection list view

type MultiListView a b = MultiListBox (CMultiListView a b) Source

Pointer to a multiple-selection list view, deriving from MultiListBox.

mkMultiListView :: Labeled x => Window a -> [Prop (MultiListView x ())] -> IO (MultiListView x ()) Source

Create a multiple-selection list view. The item type (x) must be an instance of Labeled to show each item's label. Use attribute typedSelections to access the currently selected items, and typedItems to access the list of items.

mkMultiListViewEx :: Window a -> (x -> String) -> [Prop (MultiListView x ())] -> IO (MultiListView x ()) Source

Create a multiple-selection list view. A function of type (x -> String) maps items onto labels. Use attribute typedSelections to access the currently selected items, and typedItems to access the list of items.

Choice view

type ChoiceView a b = Choice (CChoiceView a b) Source

Pointer to a choice view, deriving from Choice.

mkChoiceView :: Labeled x => Window a -> [Prop (ChoiceView x ())] -> IO (ChoiceView x ()) Source

Create a choice view to select one item from a list of typed items. The item type (x) must be an instance of Labeled to show each item's label. Use attribute typedMaybeSelection to access the currently selected item, and typedItems to access the list of items.

mkChoiceViewEx :: Window a -> (x -> String) -> Style -> [Prop (ChoiceView x ())] -> IO (ChoiceView x ()) Source

Create a choice view to select one item from a list of typed items. A function of type (x -> String) maps items onto labels. Use attribute typedMaybeSelection to access the currently selected item, and typedItems to access the list of items.

Value entry

type ValueEntry x b = TextCtrl (CValueEntry x b) Source

Pointer to a choice view, deriving from TextCtrl.

mkValueEntry :: (Show x, Read x) => Window b -> [Prop (ValueEntry x ())] -> IO (ValueEntry x ()) Source

Create a single-line value entry control. The value type (x) must be an instance of Show and Read to present a value as a string in the entry and parse the string from the entry back to (maybe) a value. Use typedValue to access the value. Note: alignment has to be set at creation time (or the entry has default alignment (=left) ).

mkValueEntryEx :: Window b -> (x -> String) -> (String -> Maybe x) -> [Prop (ValueEntry x ())] -> IO (ValueEntry x ()) Source

Create a single-line value entry control. The two functions of type (x -> String) and (String -> Maybe x) are used to present a value as a string in the entry and parse the string from the entry back to (maybe) a value. Use typedValue to access the value. Note: alignment has to be set at creation time (or the entry has default alignment (=left) ).