| Copyright | (c) Martijn Schrage 2005 |
|---|---|
| Maintainer | martijn@cs.uu.nl |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell98 |
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.
- class Labeled x where
- class TypedValued x w | w -> x where
- typedValue :: Attr w (Maybe x)
- class Items w String => TypedItems x w | w -> x where
- typedItems :: Attr w [x]
- class Selection w => TypedSelection x w | w -> x where
- typedSelection :: Attr w x
- class Selection w => TypedMaybeSelection x w | w -> x where
- typedMaybeSelection :: Attr w (Maybe x)
- class Selections w => TypedSelections x w | w -> x where
- typedSelections :: Attr w [x]
- class Observable w where
- type RadioView x b = RadioBox (CRadioView x b)
- mkRadioView :: Labeled x => Window a -> Orientation -> [x] -> [Prop (RadioView x ())] -> IO (RadioView x ())
- mkRadioViewEx :: Window a -> (x -> String) -> Orientation -> [x] -> [Prop (RadioView x ())] -> IO (RadioView x ())
- type ListView a b = SingleListBox (CListView a b)
- mkListView :: Labeled x => Window a -> [Prop (ListView x ())] -> IO (ListView x ())
- mkListViewEx :: Window a -> (x -> String) -> [Prop (ListView x ())] -> IO (ListView x ())
- type MultiListView a b = MultiListBox (CMultiListView a b)
- mkMultiListView :: Labeled x => Window a -> [Prop (MultiListView x ())] -> IO (MultiListView x ())
- mkMultiListViewEx :: Window a -> (x -> String) -> [Prop (MultiListView x ())] -> IO (MultiListView x ())
- type ChoiceView a b = Choice (CChoiceView a b)
- mkChoiceView :: Labeled x => Window a -> [Prop (ChoiceView x ())] -> IO (ChoiceView x ())
- mkChoiceViewEx :: Window a -> (x -> String) -> Style -> [Prop (ChoiceView x ())] -> IO (ChoiceView x ())
- type ValueEntry x b = TextCtrl (CValueEntry x b)
- mkValueEntry :: (Show x, Read x) => Window b -> [Prop (ValueEntry x ())] -> IO (ValueEntry x ())
- mkValueEntryEx :: Window b -> (x -> String) -> (String -> Maybe x) -> [Prop (ValueEntry x ())] -> IO (ValueEntry x ())
Classes
The labeled class is used by mkRadioView, mkListView, mkMultiListView, and
mkChoiceView for conveniently passing the function that maps an item onto its label.
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
| TypedValued x (ValueEntry x ()) |
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
| TypedItems x (ChoiceView x ()) | |
| TypedItems x (MultiListView x ()) | |
| TypedItems x (ListView x ()) | |
| TypedItems x (RadioView x ()) |
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
| TypedSelection x (RadioView x ()) |
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.
Methods
typedMaybeSelection :: Attr w (Maybe x) Source
Instances
| TypedMaybeSelection x (ChoiceView x ()) | |
| TypedMaybeSelection x (ListView 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
| TypedSelections x (MultiListView x ()) |
class Observable w where Source
Instances
| Observable (TextCtrl a) |
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.
- Instances:
TypedSelections,TypedItems,Sorted,Selecting,Selections,Items--Textual,Literate,Dimensions,Colored,Visible,Child,Able,Tipped,Identity,Styled,Reactive,Paint.
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.
- Instances:
TypedSelections,TypedItems,Sorted,Selecting,Selections,Items--Textual,Literate,Dimensions,Colored,Visible,Child,Able,Tipped,Identity,Styled,Reactive,Paint.
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) ).