wx-0.92.3.0: wxHaskell

Copyright(c) Daan Leijen 2003
LicensewxWindows
Maintainerwxhaskell-devel@lists.sourceforge.net
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Graphics.UI.WX.Attributes

Contents

Description

Widgets w can have attributes of type a represented by the type Attr w a. An example of an attribute is text with type:

text :: Attr (Window a) String

This means that any object derived from Window has a 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 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.

Synopsis

Attributes

data Attr w a Source #

Widgets w can have attributes of type a.

Instances

Show a => Show (Attr w a) Source # 

Methods

showsPrec :: Int -> Attr w a -> ShowS #

show :: Attr w a -> String #

showList :: [Attr w a] -> ShowS #

data Prop w Source #

A property of a widget w is an attribute that is already associated with a value. .

Constructors

(Attr w a) := a infixr 0

Assign a value to an attribute.

(Attr w a) :~ (a -> a) infixr 0

Apply an update function to an attribute.

(Attr w a) ::= (w -> a) infixr 0

Assign a value to an attribute with the widget as argument.

(Attr w a) ::~ (w -> a -> a) infixr 0

Apply an update function to an attribute with the widget as an argument.

Instances

Show a => Show (Prop a) Source # 

Methods

showsPrec :: Int -> Prop a -> ShowS #

show :: Prop a -> String #

showList :: [Prop a] -> ShowS #

type ReadAttr w a = Attr w a Source #

A read-only attribute. Just for documentation purposes.

type WriteAttr w a = Attr w a Source #

A write-only attribute. Just for documentation purposes.

type CreateAttr w a = Attr w a Source #

An attribute that should be specified at creation time. Just for documentation purposes.

get :: w -> Attr w a -> IO a Source #

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 a Source #

Set the value of an attribute and return the old value.

mapAttr :: (a -> b) -> (a -> b -> a) -> Attr w a -> Attr w b Source #

(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 a Source #

(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 a Source #

Create a new attribute with a specified name, getter and setter function.

readAttr :: String -> (w -> IO a) -> ReadAttr w a Source #

Define a read-only attribute.

writeAttr :: String -> (w -> a -> IO ()) -> WriteAttr w a Source #

Define a write-only attribute.

nullAttr :: String -> WriteAttr w a Source #

A dummy attribute.

constAttr :: Typeable a => String -> a -> Attr w a Source #

A constant attribute.

makeAttr :: String -> (w -> IO a) -> (w -> a -> IO ()) -> (w -> (a -> a) -> IO a) -> Attr w a Source #

Create a new attribute with a specified name, getter, setter, and updater function.

Reflection

attrName :: Attr w a -> String Source #

Retrieve the name of an attribute

propName :: Prop w -> String Source #

Retrieve the name of a property.

containsProperty :: Attr w a -> [Prop w] -> Bool Source #

Is a certain property in a list of properties?

Reflective attributes

reflectiveAttr :: Typeable a => String -> (w -> IO a) -> (w -> a -> IO ()) -> Attr w a Source #

Create a reflective attribute with a specified name: value can possibly be 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 a Source #

Create a reflective attribute with a specified name: value can possibly be 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] -> b Source #

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 -> a Source #

Transform the properties based on a style property.

withStylePropertyNot :: Attr w Bool -> Style -> ([Prop w] -> Style -> a) -> [Prop w] -> Style -> a Source #

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 

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 a Source #

Cast attributes.

castProp :: (v -> w) -> Prop w -> Prop v Source #

Cast properties

castProps :: (v -> w) -> [Prop w] -> [Prop v] Source #

Cast a list of properties.