wx-0.10.1: wxHaskell is a portable and native GUI library for Haskell.Source codeContentsIndex
Graphics.UI.WX.Attributes
Contents
Attributes
Internal
Attributes
Reflection
Reflective attributes
Filter
Cast
Description
Synopsis
data Attr w a
data Prop w
= forall a . (Attr w a) := a
| forall a . (Attr w a) :~ (a -> a)
| forall a . (Attr w a) ::= (w -> a)
| forall a . (Attr w a) ::~ (w -> a -> a)
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
data Attr w a Source
Widgets w can have attributes of type a.
data Prop w Source
A property of a widget w is an attribute that is already associated with a value. .
Constructors
forall a . (Attr w a) := aAssign 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 ReadAttr w a = Attr w aSource
A read-only attribute. Just for documentation purposes.
type WriteAttr w a = Attr w aSource
A write-only attribute. Just for documentation purposes.
type CreateAttr w a = Attr w aSource
An attribute that should be specified at creation time. Just for documentation purposes.
get :: w -> Attr w a -> IO aSource

Get the value of an attribute

 t <- get w text
set :: w -> [Prop w] -> IO ()Source

Set a list of properties.

 set w [text := "Hi"]
swap :: w -> Attr w a -> a -> IO aSource
Set the value of an attribute and return the old value.
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.
readAttr :: String -> (w -> IO a) -> ReadAttr w aSource
Define a read-only attribute.
writeAttr :: String -> (w -> a -> IO ()) -> WriteAttr w aSource
Define a write-only attribute.
nullAttr :: String -> WriteAttr w aSource
A dummy attribute.
constAttr :: Typeable a => String -> a -> Attr w aSource
A constant attribute.
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
attrName :: Attr w a -> StringSource
Retrieve the name of an attribute
propName :: Prop w -> StringSource
Retrieve the name of a property.
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
data PropValue a Source
Property value: used when retrieving a property from a list.
Constructors
PropValue a
PropModify (a -> a)
PropNone
show/hide Instances
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.
Cast
castAttr :: (v -> w) -> Attr w a -> Attr v aSource
Cast attributes.
castProp :: (v -> w) -> Prop w -> Prop vSource
Cast properties
castProps :: (v -> w) -> [Prop w] -> [Prop v]Source
Cast a list of properties.
Produced by Haddock version 2.1.0