wx-0.92.0.0: wxHaskell

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

Graphics.UI.WX.Types

Contents

Description

Basic types.

Synopsis

Basic Types

data Orientation :: *

The orientation of a widget.

Constructors

Horizontal 
Vertical 

Objects

(#) :: obj -> (obj -> a) -> a infix 5

Reverse application, i.e. x # f = f x. Useful for an object oriented style of programming.

(frame # frameSetTitle) "hi"

feed :: a -> (a -> b) -> b Source

Inverse application, i.e. feed x f = f x.

feed2 :: a -> b -> (a -> b -> c) -> c Source

Composed Inverse application, i.e. feed2 x y f = f x y.

data Object a :: * -> *

An Object a is a pointer to an object of type a. The a parameter is used to encode the inheritance relation. When the type parameter is unit (), it denotes an object of exactly that class, when the parameter is a type variable a, it specifies an object that is at least an instance of that class. For example in wxWidgets, we have the following class hierarchy:

EvtHandler
  |- Window
       |- Frame
       |- Control
           |- Button
           |- Radiobox

In wxHaskell, all the creation functions will return objects of exactly that class and use the () type:

frameCreate :: Window a -> ... -> IO (Frame ())
buttonCreate :: Window a -> ... -> IO (Button ())
...

In contrast, all the this (or self) pointers of methods can take objects of any instance of that class and have a type variable, for example:

windowSetClientSize :: Window a -> Size -> IO ()
controlSetLabel     :: Control a -> String -> IO ()
buttonSetDefault    :: Button a -> IO ()

This means that we can use windowSetClientSize on any window, including buttons and frames, but we can only use controlSetLabel on controls, not including frames.

In wxHaskell, this works since a Frame () is actually a type synonym for Window (CFrame ()) (where CFrame is an abstract data type). We can thus pass a value of type Frame () to anything that expects some Window a. For a button this works too, as it is a synonym for Control (CButton ()) which is in turn a synonym for Window (CControl (CButton ())). Note that we can't pass a frame to something that expects a value of type Control a. Of course, a Window a is actually a type synonym for EvtHandler (CWindow a). If you study the documentation in Graphics.UI.WX.Classes closely, you can discover where this chain ends :-).

Objects are not automatically deleted. Normally you can use a delete function like windowDelete to delete an object. However, almost all objects in the wxWidgets library are automatically deleted by the library. The only objects that should be used with care are resources as bitmaps, fonts and brushes.

Instances

Able Timer 
Commanding Timer 
Eq (Object a) 
Ord (Object a) 
Show (Object a) 
Widget (Window a) 
Form (Panel a) 
Form (Frame a) 
Form (Dialog a) 
HasDefault (TopLevelWindow a) 
Sized (Window a) 
Sized (Bitmap a) 
Sized (Image a) 
Selections (MultiListBox a) 
Selection (Slider a) 
Selection (Gauge a) 
Selection (SpinCtrl a) 
Selection (RadioBox a) 
Selection (Choice ()) 
Selection (ComboBox a) 
Selection (SingleListBox a) 
Tipped (Window a) 
Styled (Window a) 
Identity (Window a) 
Identity (MenuItem a) 
Checkable (ToggleButton a) 
Checkable (CheckBox a) 
Checkable (MenuItem a) 
Help (MenuItem a) 
Able (Window a) 
Able (MenuItem a) 
Framed (TopLevelWindow a) 
Closeable (Frame a) 
Child (Window a) 
Bordered (Window a) 
Parent (Window a) 
Visible (Window a) 
Colored (Window a) 
Colored (DC a) 
Dimensions (Window a) 
Literate (Window a) 
Literate (DC a) 
Pictured (BitmapToggleButton a) 
Pictured (BitmapButton a) 
Pictured (TopLevelWindow a) 
Textual (Window a) 
Textual (Menu a) 
Textual (MenuItem a) 
Media (MediaCtrl a) 
Media (Sound a) 
Paint (Window a) 
Reactive (Window a) 
Updating (TextCtrl a) 
Updating (ComboBox a) 
Commanding (Slider a) 
Commanding (ToggleButton a) 
Commanding (TextCtrl a) 
Commanding (Button a) 
Commanding (ComboBox a) 
Commanding (CheckBox a) 
Commanding (MenuItem a) 
Selecting (SpinCtrl a) 
Selecting (RadioBox a) 
Selecting (ListBox a) 
Selecting (Choice ()) 
Selecting (ComboBox a) 
Sorted (ListBox a) 
Sorted (Choice a) 
IsDate (DateTime ()) 
Wrapped (TextCtrl a) 
Aligned (TextCtrl a) 
Brushed (DC a) 
Drawn (DC a) 
Items (RadioBox a) String 
Items (ListBox a) String 
Items (Choice a) String 
Items (ListCtrl a) [String] 

objectNull :: Object a

A null object. Use with care.

objectIsNull :: Object a -> Bool

Test for null object.

objectCast :: Object a -> Object b

Cast an object to another type. Use with care.

objectIsManaged :: Object a -> Bool

Is this a managed object?

objectDelete :: WxObject a -> IO ()

Delete a wxObject, works for managed and unmanaged objects.

Identifiers

type Id = Int

An Id is used to identify objects during event handling.

idAny :: Id

When creating a new window you may specify idAny to let wxWidgets assign an unused identifier to it automatically. Furthermore, it can be used in an event connection to handle events for any identifier.

idCreate :: IO Id

Create a new unique identifier.

Mutable variables

type Var a = TVar a

A mutable variable. Use this instead of MVars or IORefs to accomodate for future expansions with possible concurrency.

varCreate :: a -> IO (Var a)

Create a fresh mutable variable.

varGet :: Var a -> IO a

Get the value of a mutable variable.

varSet :: Var a -> a -> IO ()

Set the value of a mutable variable.

varUpdate :: Var a -> (a -> a) -> IO a

Update the value of a mutable variable and return the old value.

varSwap :: Var a -> a -> IO a

Swap the value of a mutable variable.

Bits

class Eq b => BitMask b where Source

Data types that can be represented through a bit mask. Only the assocBitMask method is required for a new instance.

Minimal complete definition

assocBitMask

Methods

assocBitMask :: [(b, Int)] Source

Give the association between the constructors and the bits. If a constructor corresponds to no bits set, it should come as the last element.

toBitMask :: b -> Int Source

Convert to a bitmask

fromBitMask :: Int -> b Source

Convert from a bitmask

setBitMask :: b -> Int -> Int Source

Set the correct bits corresponding to a constructor in a mask.

mask :: BitMask b => [b] -> Int Source

Create a bitmask from a list of types.

(.+.) :: Bits a => a -> a -> a infixl 5

Bitwise or of two bit masks.

(.-.) :: Bits a => a -> a -> a infixl 5

Unset certain bits in a bitmask.

bits :: (Num a, Bits a) => [a] -> a

Bitwise or of a list of bit masks.

bitsSet :: Bits a => a -> a -> Bool

(bitsSet mask i) tests if all bits in mask are also set in i.

Booleans

Misc.

type Style = Int

A Style is normally used as a flag mask to specify some window style

type EventId = Int

An EventId is identifies specific events.

data TreeItem :: *

Identifies tree items. Note: Replaces the TreeItemId object and takes automatically care of allocation issues.

Graphical types

Colors

data Color :: *

An abstract data type to define colors.

Note: Haddock 0.8 and 0.9 doesn't support GeneralizedNewtypeDeriving. So, This class doesn't have IArray class's unboxed array instance now. If you want to use this type with unboxed array, you must write code like this.

{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving, MultiParamTypeClasses #-}
import Graphics.UI.WXCore.WxcTypes
...
deriving instance IArray UArray Color

We can't derive MArray class's unboxed array instance this way. This is a bad point of current MArray class definition.

Instances

rgb :: Integral a => a -> a -> a -> Color

Create a color from a red/green/blue triple.

colorRGB :: Integral a => a -> a -> a -> Color

Create a color from a red/green/blue triple.

colorRed :: Num a => Color -> a

Returns a red color component

colorGreen :: Num a => Color -> a

Returns a green color component

colorBlue :: Num a => Color -> a

Returns a blue color component

System colors

data SystemColor :: *

System Colors.

Constructors

ColorScrollBar

The scrollbar grey area.

ColorBackground

The desktop colour.

ColorActiveCaption

Active window caption.

ColorInactiveCaption

Inactive window caption.

ColorMenu

Menu background.

ColorWindow

Window background.

ColorWindowFrame

Window frame.

ColorMenuText

Menu text.

ColorWindowText

Text in windows.

ColorCaptionText

Text in caption, size box and scrollbar arrow box.

ColorActiveBorder

Active window border.

ColorInactiveBorder

Inactive window border.

ColorAppWorkspace

Background colour MDI -- ^applications.

ColorHighlight

Item(s) selected in a control.

ColorHighlightText

Text of item(s) selected in a control.

ColorBtnFace

Face shading on push buttons.

ColorBtnShadow

Edge shading on push buttons.

ColorGrayText

Greyed (disabled) text.

ColorBtnText

Text on push buttons.

ColorInactiveCaptionText

Colour of text in active captions.

ColorBtnHighlight

Highlight colour for buttons (same as 3DHILIGHT).

Color3DDkShadow

Dark shadow for three-dimensional display elements.

Color3DLight

Light colour for three-dimensional display elements.

ColorInfoText

Text colour for tooltip controls.

ColorInfoBk

Background colour for tooltip controls.

ColorDesktop

Same as BACKGROUND.

Color3DFace

Same as BTNFACE.

Color3DShadow

Same as BTNSHADOW.

Color3DHighlight

Same as BTNHIGHLIGHT.

Color3DHilight

Same as BTNHIGHLIGHT.

ColorBtnHilight

Same as BTNHIGHLIGHT.

Instances

colorSystem :: SystemColor -> Color

Convert a system color to a color.

Font

data FontStyle :: *

Font descriptor. The font is normally specified thru the FontFamily, giving some degree of portability. The _fontFace can be used to specify the exact (platform dependent) font.

Note that the original wxWidgets FontStyle is renamed to FontShape.

Constructors

FontStyle 

Fields

_fontSize :: !Int
 
_fontFamily :: !FontFamily
 
_fontShape :: !FontShape
 
_fontWeight :: !FontWeight
 
_fontUnderline :: !Bool
 
_fontFace :: !String

normally ""

_fontEncoding :: !Int

normally wxFONTENCODING_DEFAULT

data FontFamily :: *

Standard font families.

Constructors

FontDefault

A system default font.

FontDecorative

Decorative font.

FontRoman

Formal serif font.

FontScript

Hand writing font.

FontSwiss

Sans-serif font.

FontModern

Fixed pitch font.

FontTeletype

A teletype (i.e. monospaced) font

data FontShape :: *

The font style.

data FontWeight :: *

The font weight.

fontDefault :: FontStyle

Default 10pt font.

fontSwiss :: FontStyle

Default 10pt sans-serif font.

fontSmall :: FontStyle

Default 8pt font.

fontItalic :: FontStyle

Default 10pt italic.

fontFixed :: FontStyle

Monospaced font, 10pt.

Brush

data BrushStyle :: *

Brush style.

Constructors

BrushStyle 

data BrushKind :: *

Brush kind.

Constructors

BrushTransparent

No filling

BrushSolid

Solid color

BrushHatch

Hatch pattern

BrushStipple

Bitmap pattern (on win95 only 8x8 bitmaps are supported)

Fields

_brushBitmap :: !(Bitmap ())
 

data HatchStyle :: *

Hatch style.

Constructors

HatchBDiagonal

Backward diagonal

HatchCrossDiag

Crossed diagonal

HatchFDiagonal

Forward diagonal

HatchCross

Crossed orthogonal

HatchHorizontal

Horizontal

HatchVertical

Vertical

brushDefault :: BrushStyle

Default brush (transparent, black).

brushTransparent :: BrushStyle

A transparent brush.

Pen

data PenStyle :: *

Pen style.

Constructors

PenStyle 

Instances

data PenKind :: *

Pen kinds.

Constructors

PenTransparent

No edge.

PenSolid 
PenDash 

Fields

_penDash :: !DashStyle
 
PenHatch 

Fields

_penHatch :: !HatchStyle
 
PenStipple

_penColor is ignored

Fields

_penBitmap :: !(Bitmap ())
 

Instances

data CapStyle :: *

Cap style

Constructors

CapRound

End points are rounded

CapProjecting 
CapButt 

Instances

data JoinStyle :: *

Join style.

Constructors

JoinRound

Corners are rounded

JoinBevel

Corners are bevelled

JoinMiter

Corners are blocked

data DashStyle :: *

Dash style

penDefault :: PenStyle

Default pen (PenStyle PenSolid black 1 CapRound JoinRound)

penColored :: Color -> Int -> PenStyle

A solid pen with a certain color and width.

penTransparent :: PenStyle

A transparent pen.

Geometrical types

Points

data Num a => Point2 a :: * -> *

A point has an x and y coordinate. Coordinates are normally relative to the upper-left corner of their view frame, where a positive x goes to the right and a positive y to the bottom of the view.

Constructors

Point 

Fields

pointX :: !a

x component of a point.

pointY :: !a

y component of a point.

Instances

(Eq a, Num a) => Eq (Point2 a) 
(Num a, Ord a) => Ord (Point2 a) 
(Num a, Read a) => Read (Point2 a) 
(Num a, Show a) => Show (Point2 a) 
Ix (Point2 Int) 
Typeable (* -> *) Point2 

point :: Num a => a -> a -> Point2 a

Construct a point.

pt :: Num a => a -> a -> Point2 a

Shorter function to construct a point.

pointZero :: Num a => Point2 a

Point at the origin.

pointNull :: Num a => Point2 a

A null point is not a legal point (x and y are -1) and can be used for some wxWidgets functions to select a default point.

pointMove :: Num a => Vector2 a -> Point2 a -> Point2 a

pointMoveBySize :: Num a => Point2 a -> Size2D a -> Point2 a

pointAdd :: Num a => Point2 a -> Point2 a -> Point2 a

pointSub :: Num a => Point2 a -> Point2 a -> Point2 a

pointScale :: Num a => Point2 a -> a -> Point2 a

Sizes

type Size = Size2D Int

data Num a => Size2D a :: * -> *

A Size has a width and height.

Constructors

Size 

Fields

sizeW :: !a

the width of a size

sizeH :: !a

the height of a size

Instances

(Eq a, Num a) => Eq (Size2D a) 
(Num a, Show a) => Show (Size2D a) 
Typeable (* -> *) Size2D 

sz :: Num a => a -> a -> Size2D a

Short function to construct a size

sizeFromVec :: Num a => Vector2 a -> Size2D a

sizeZero :: Num a => Size2D a

sizeNull :: Num a => Size2D a

A null size is not a legal size (width and height are -1) and can be used for some wxWidgets functions to select a default size.

sizeEncloses :: (Num a, Ord a) => Size2D a -> Size2D a -> Bool

Returns True if the first size totally encloses the second argument.

sizeMin :: (Num a, Ord a) => Size2D a -> Size2D a -> Size2D a

The minimum of two sizes.

sizeMax :: (Num a, Ord a) => Size2D a -> Size2D a -> Size2D a

The maximum of two sizes.

Vectors

data Num a => Vector2 a :: * -> *

A vector with an x and y delta.

Constructors

Vector 

Fields

vecX :: !a

delta-x component of a vector

vecY :: !a

delta-y component of a vector

Instances

(Eq a, Num a) => Eq (Vector2 a) 
(Num a, Read a) => Read (Vector2 a) 
(Num a, Show a) => Show (Vector2 a) 
Typeable (* -> *) Vector2 

vector :: Num a => a -> a -> Vector2 a

Construct a vector.

vec :: Num a => a -> a -> Vector2 a

Short function to construct a vector.

vecZero :: Num a => Vector2 a

A zero vector

vecNull :: Num a => Vector2 a

A null vector has a delta x and y of -1 and can be used for some wxWidgets functions to select a default vector.

vecNegate :: Num a => Vector2 a -> Vector2 a

vecAdd :: Num a => Vector2 a -> Vector2 a -> Vector2 a

vecSub :: Num a => Vector2 a -> Vector2 a -> Vector2 a

vecScale :: Num a => Vector2 a -> a -> Vector2 a

vecBetween :: Num a => Point2 a -> Point2 a -> Vector2 a

Rectangles

type Rect = Rect2D Int

data Num a => Rect2D a :: * -> *

A rectangle is defined by the left x coordinate, the top y coordinate, the width and the height.

Constructors

Rect 

Fields

rectLeft :: !a
 
rectTop :: !a
 
rectWidth :: !a
 
rectHeight :: !a
 

Instances

(Eq a, Num a) => Eq (Rect2D a) 
(Num a, Read a) => Read (Rect2D a) 
(Num a, Show a) => Show (Rect2D a) 
Typeable (* -> *) Rect2D 

rectTopLeft :: Num a => Rect2D a -> Point2 a

rectTopRight :: Num a => Rect2D a -> Point2 a

rectBottom :: Num a => Rect2D a -> a

rectRight :: Num a => Rect2D a -> a

rect :: Num a => Point2 a -> Size2D a -> Rect2D a

Create a rectangle at a certain (upper-left) point with a certain size.

rectBetween :: (Num a, Ord a) => Point2 a -> Point2 a -> Rect2D a

Construct a (positive) rectangle between two (arbitrary) points.

rectFromSize :: Num a => Size2D a -> Rect2D a

Create a rectangle of a certain size with the upper-left corner at (pt 0 0).

rectZero :: Num a => Rect2D a

An empty rectangle at (0,0).

rectNull :: Num a => Rect2D a

An null rectangle is not a valid rectangle (Rect -1 -1 -1 -1) but can used for some wxWidgets functions to select a default rectangle. (i.e. frameCreate).

rectSize :: Num a => Rect2D a -> Size2D a

Get the size of a rectangle.

rectIsEmpty :: (Num a, Eq a) => Rect2D a -> Bool

rectContains :: (Num a, Ord a) => Rect2D a -> Point2 a -> Bool

rectMoveTo :: Num a => Rect2D a -> Point2 a -> Rect2D a

rectStretchTo :: Num a => Rect2D a -> Size2D a -> Rect2D a

rectMove :: Num a => Rect2D a -> Vector2 a -> Rect2D a

rectOverlaps :: (Num a, Ord a) => Rect2D a -> Rect2D a -> Bool

rectsDiff :: (Num a, Ord a) => Rect2D a -> Rect2D a -> [Rect2D a]

A list with rectangles that constitute the difference between two rectangles.

rectUnion :: (Num a, Ord a) => Rect2D a -> Rect2D a -> Rect2D a

rectOverlap :: (Num a, Ord a) => Rect2D a -> Rect2D a -> Rect2D a

The intersection between two rectangles.

rectUnions :: (Num a, Ord a) => [Rect2D a] -> Rect2D a

IO Control

unitIO :: IO a -> IO ()

Ignore the result of an IO action.

bracket

Arguments

:: IO a

computation to run first (acquire resource)

-> (a -> IO b)

computation to run last (release resource)

-> (a -> IO c)

computation to run in-between (use resource)

-> IO c 

Properly release resources, even in the event of an exception.

bracket_

Arguments

:: IO a

computation to run first (acquire resource)

-> IO b

computation to run last (release resource)

-> IO c

computation to run in-between (use resource)

-> IO c 

Specialized variant of bracket where the return value is not required.

finally

Arguments

:: IO a

computation to run first

-> IO b

computation to run last (release resource)

-> IO a 

Run some computation afterwards, even if an exception occurs.

finalize

Arguments

:: IO b

computation to run last (release resource)

-> IO a

computation to run first

-> IO a 

Run some computation afterwards, even if an exception occurs. Equals finally but with the arguments swapped.

when :: Bool -> IO () -> IO ()

Perform an action when a test succeeds.