Portability | portable |
---|---|
Stability | provisional |
Maintainer | wxhaskell-devel@lists.sourceforge.net |
Widgets w
can have attributes of type a
represented by the type Attr
w a
.
An example of an attribute is Graphics.UI.WX.Classes.text
with type:
text :: Attr (Window a) String
This means that any object derived from Window
has a Graphics.UI.WX.Classes.text
attribute of type String
.
An attribute can be read with the get
function:
get w title :: IO String
When an attribute is associated with a value, we call it a property of type Prop
w
.
Properties are constructed by assigning a value to an attribute with the (:=
) constructor:
text := "hello world" :: Prop (Window a)
A list of properties can be set with the set
function:
set w [text := "Hi"] :: IO ()
The (:~
) constructor is used to transform an attribute value with an update function.
For example, the interval
on a timer can be doubled with the following expression.
set timer [interval :~ (*2)]
The functions get
, set
, (:=
), and (:~
) are polymorphic and work for all widgets, but
the text
attribute just works for windows. Many attributes work for different kind
of objects and are organised into type classes. Actually, the real type of the
Graphics.UI.WX.Classes.text
attribute is:
Textual w => Attr w String
and Window
derived objects are part of this class:
instance Textual (Window a)
But also menus and status fields:
instance Textual (Menu a) instance Textual (StatusField)
Sometimes, it is convenient to also get a reference to the object itself when setting
a property. The operators (::=
) and (::~
) provide this reference.
- data Attr w a
- data Prop w
- type ReadAttr w a = Attr w a
- type WriteAttr w a = Attr w a
- type CreateAttr w a = Attr w a
- get :: w -> Attr w a -> IO a
- set :: w -> [Prop w] -> IO ()
- swap :: w -> Attr w a -> a -> IO a
- mapAttr :: (a -> b) -> (a -> b -> a) -> Attr w a -> Attr w b
- mapAttrW :: (v -> w) -> Attr w a -> Attr v a
- newAttr :: String -> (w -> IO a) -> (w -> a -> IO ()) -> Attr w a
- readAttr :: String -> (w -> IO a) -> ReadAttr w a
- writeAttr :: String -> (w -> a -> IO ()) -> WriteAttr w a
- nullAttr :: String -> WriteAttr w a
- constAttr :: Typeable a => String -> a -> Attr w a
- makeAttr :: String -> (w -> IO a) -> (w -> a -> IO ()) -> (w -> (a -> a) -> IO a) -> Attr w a
- attrName :: Attr w a -> String
- propName :: Prop w -> String
- containsProperty :: Attr w a -> [Prop w] -> Bool
- reflectiveAttr :: Typeable a => String -> (w -> IO a) -> (w -> a -> IO ()) -> Attr w a
- createAttr :: Typeable a => String -> (w -> IO a) -> (w -> a -> IO ()) -> CreateAttr w a
- withProperty :: Typeable a => Attr w a -> a -> (a -> [Prop w] -> b) -> [Prop w] -> b
- findProperty :: Typeable a => Attr w a -> a -> [Prop w] -> Maybe (a, [Prop w])
- withStyleProperty :: Attr w Bool -> Style -> ([Prop w] -> Style -> a) -> [Prop w] -> Style -> a
- withStylePropertyNot :: Attr w Bool -> Style -> ([Prop w] -> Style -> a) -> [Prop w] -> Style -> a
- data PropValue a
- = PropValue a
- | PropModify (a -> a)
- | PropNone
- filterProperty :: Typeable a => Attr w a -> [Prop w] -> (PropValue a, [Prop w])
- castAttr :: (v -> w) -> Attr w a -> Attr v a
- castProp :: (v -> w) -> Prop w -> Prop v
- castProps :: (v -> w) -> [Prop w] -> [Prop v]
Attributes
A property of a widget w
is an attribute that
is already associated with a value. .
forall a . (Attr w a) := a | Assign a value to an attribute. |
forall a . (Attr w a) :~ (a -> a) | Apply an update function to an attribute. |
forall a . (Attr w a) ::= (w -> a) | Assign a value to an attribute with the widget as argument. |
forall a . (Attr w a) ::~ (w -> a -> a) | Apply an update function to an attribute with the widget as an argument. |
type CreateAttr w a = Attr w aSource
An attribute that should be specified at creation time. Just for documentation purposes.
mapAttr :: (a -> b) -> (a -> b -> a) -> Attr w a -> Attr w bSource
(mapAttr get set attr
) maps an attribute of Attr w a
to
Attr w b
where (get :: a -> b
) is used when the attribute is
requested and (set :: a -> b -> a
) is applied to current
value when the attribute is set.
mapAttrW :: (v -> w) -> Attr w a -> Attr v aSource
(mapAttrW conv attr
) maps an attribute of Attr w a
to
Attr v a
where (conv :: v -> w
) is used to convert a widget
v
into a widget of type w
.
Internal
Attributes
newAttr :: String -> (w -> IO a) -> (w -> a -> IO ()) -> Attr w aSource
Create a new attribute with a specified name, getter and setter function.
makeAttr :: String -> (w -> IO a) -> (w -> a -> IO ()) -> (w -> (a -> a) -> IO a) -> Attr w aSource
Create a new attribute with a specified name, getter, setter, and updater function.
Reflection
containsProperty :: Attr w a -> [Prop w] -> BoolSource
Is a certain property in a list of properties?
Reflective attributes
reflectiveAttr :: Typeable a => String -> (w -> IO a) -> (w -> a -> IO ()) -> Attr w aSource
Create a reflective attribute with a specified name: value can possibly
retrieved using getPropValue
. Note: the use of this function is discouraged
as it leads to non-compositional code.
createAttr :: Typeable a => String -> (w -> IO a) -> (w -> a -> IO ()) -> CreateAttr w aSource
Create a reflective attribute with a specified name: value can possibly
retrieved using getPropValue
. Note: the use of this function is discouraged
as it leads to non-compositional code.
withProperty :: Typeable a => Attr w a -> a -> (a -> [Prop w] -> b) -> [Prop w] -> bSource
Try to find a property value and call the contination function with that value and the property list witht the searched property removed. If the property is not found, use the default value and the unchanged property list.
findProperty :: Typeable a => Attr w a -> a -> [Prop w] -> Maybe (a, [Prop w])Source
Try to find a property value. Return |Nothing| if not found at all.
withStyleProperty :: Attr w Bool -> Style -> ([Prop w] -> Style -> a) -> [Prop w] -> Style -> aSource
Transform the properties based on a style property.
withStylePropertyNot :: Attr w Bool -> Style -> ([Prop w] -> Style -> a) -> [Prop w] -> Style -> aSource
Transform the properties based on a style property. The flag is interpreted negatively, i.e. |True| removes the bit instead of setting it.
Filter
Property value: used when retrieving a property from a list.
PropValue a | |
PropModify (a -> a) | |
PropNone |
filterProperty :: Typeable a => Attr w a -> [Prop w] -> (PropValue a, [Prop w])Source
Retrieve the value of a property and the list with the property removed.