Portability | portable |
---|---|
Stability | provisional |
Maintainer | wxhaskell-devel@lists.sourceforge.net |
Basic types.
- data Orientation
- = Horizontal
- | Vertical
- (#) :: obj -> (obj -> a) -> a
- feed :: a -> (a -> b) -> b
- feed2 :: a -> b -> (a -> b -> c) -> c
- data Object a
- objectNull :: Object a
- objectIsNull :: Object a -> Bool
- objectCast :: Object a -> Object b
- objectIsManaged :: Object a -> Bool
- objectDelete :: WxObject a -> IO ()
- type Id = Int
- idAny :: Id
- idCreate :: IO Id
- type Var a = TVar a
- varCreate :: a -> IO (Var a)
- varGet :: Var a -> IO a
- varSet :: Var a -> a -> IO ()
- varUpdate :: Var a -> (a -> a) -> IO a
- varSwap :: Var a -> a -> IO a
- class Eq b => BitMask b where
- assocBitMask :: [(b, Int)]
- toBitMask :: b -> Int
- fromBitMask :: Int -> b
- setBitMask :: b -> Int -> Int
- mask :: BitMask b => [b] -> Int
- (.+.) :: Int -> Int -> Int
- (.-.) :: Int -> BitFlag -> Int
- bits :: [Int] -> Int
- bitsSet :: Int -> Int -> Bool
- toCBool :: Bool -> CBool
- fromCBool :: CBool -> Bool
- type Style = Int
- type EventId = Int
- data TreeItem
- data Color
- rgb :: Integral a => a -> a -> a -> Color
- colorRGB :: Integral a => a -> a -> a -> Color
- colorRed :: Num a => Color -> a
- colorGreen :: Num a => Color -> a
- colorBlue :: Num a => Color -> a
- black :: Color
- darkgrey :: Color
- dimgrey :: Color
- mediumgrey :: Color
- grey :: Color
- lightgrey :: Color
- white :: Color
- red :: Color
- green :: Color
- blue :: Color
- cyan :: Color
- magenta :: Color
- yellow :: Color
- data SystemColor
- = ColorScrollBar
- | ColorBackground
- | ColorActiveCaption
- | ColorInactiveCaption
- | ColorMenu
- | ColorWindow
- | ColorWindowFrame
- | ColorMenuText
- | ColorWindowText
- | ColorCaptionText
- | ColorActiveBorder
- | ColorInactiveBorder
- | ColorAppWorkspace
- | ColorHighlight
- | ColorHighlightText
- | ColorBtnFace
- | ColorBtnShadow
- | ColorGrayText
- | ColorBtnText
- | ColorInactiveCaptionText
- | ColorBtnHighlight
- | Color3DDkShadow
- | Color3DLight
- | ColorInfoText
- | ColorInfoBk
- | ColorDesktop
- | Color3DFace
- | Color3DShadow
- | Color3DHighlight
- | Color3DHilight
- | ColorBtnHilight
- colorSystem :: SystemColor -> Color
- data FontStyle = FontStyle {
- _fontSize :: !Int
- _fontFamily :: !FontFamily
- _fontShape :: !FontShape
- _fontWeight :: !FontWeight
- _fontUnderline :: !Bool
- _fontFace :: !String
- _fontEncoding :: !Int
- data FontFamily
- = FontDefault
- | FontDecorative
- | FontRoman
- | FontScript
- | FontSwiss
- | FontModern
- data FontShape
- = ShapeNormal
- | ShapeItalic
- | ShapeSlant
- data FontWeight
- fontDefault :: FontStyle
- fontSwiss :: FontStyle
- fontSmall :: FontStyle
- fontItalic :: FontStyle
- fontFixed :: FontStyle
- data BrushStyle = BrushStyle {
- _brushKind :: !BrushKind
- _brushColor :: !Color
- data BrushKind
- = BrushTransparent
- | BrushSolid
- | BrushHatch { }
- | BrushStipple {
- _brushBitmap :: !(Bitmap ())
- data HatchStyle
- brushDefault :: BrushStyle
- brushTransparent :: BrushStyle
- data PenStyle = PenStyle {}
- data PenKind
- = PenTransparent
- | PenSolid
- | PenDash { }
- | PenHatch {
- _penHatch :: !HatchStyle
- | PenStipple {
- _penBitmap :: !(Bitmap ())
- data CapStyle
- = CapRound
- | CapProjecting
- | CapButt
- data JoinStyle
- data DashStyle
- = DashDot
- | DashLong
- | DashShort
- | DashDotShort
- penDefault :: PenStyle
- penColored :: Color -> Int -> PenStyle
- penTransparent :: PenStyle
- type Point = Point2 Int
- data Num a => Point2 a = Point {}
- point :: Num a => a -> a -> Point2 a
- pt :: Num a => a -> a -> Point2 a
- pointFromVec :: Num a => Vector -> Point2 a
- pointFromSize :: Num a => Size -> Point2 a
- pointZero :: Num a => Point2 a
- pointNull :: Num a => Point2 a
- 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
- type Size = Size2D Int
- data Num a => Size2D a = Size {}
- sz :: Num a => a -> a -> Size2D a
- sizeFromPoint :: Num a => Point2 a -> Size2D a
- sizeFromVec :: Num a => Vector2 a -> Size2D a
- sizeZero :: Num a => Size2D a
- sizeNull :: Num a => Size2D a
- sizeEncloses :: (Num a, Ord a) => Size2D a -> Size2D a -> Bool
- sizeMin :: (Num a, Ord a) => Size2D a -> Size2D a -> Size2D a
- sizeMax :: (Num a, Ord a) => Size2D a -> Size2D a -> Size2D a
- type Vector = Vector2 Int
- data Num a => Vector2 a = Vector {}
- vector :: Num a => a -> a -> Vector2 a
- vec :: Num a => a -> a -> Vector2 a
- vecFromPoint :: Num a => Point2 a -> Vector2 a
- vecFromSize :: Size -> Vector
- vecZero :: Num a => Vector2 a
- vecNull :: Num a => Vector2 a
- vecNegate :: Num a => Vector2 a -> Vector2 a
- vecOrtogonal :: 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
- vecLength :: Vector -> Double
- vecLengthDouble :: Vector2 Double -> Double
- type Rect = Rect2D Int
- data Num a => Rect2D a = Rect {
- rectLeft :: !a
- rectTop :: !a
- rectWidth :: !a
- rectHeight :: !a
- rectTopLeft :: Num a => Rect2D a -> Point2 a
- rectTopRight :: Num a => Rect2D a -> Point2 a
- rectBottomLeft :: Num a => Rect2D a -> Point2 a
- rectBottomRight :: 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
- rectBetween :: (Num a, Ord a) => Point2 a -> Point2 a -> Rect2D a
- rectFromSize :: Num a => Size2D a -> Rect2D a
- rectZero :: Num a => Rect2D a
- rectNull :: Num a => Rect2D a
- rectSize :: Num a => Rect2D a -> Size2D a
- rectIsEmpty :: Num a => Rect2D a -> Bool
- rectContains :: (Num a, Ord a) => Rect2D a -> Point2 a -> Bool
- rectMoveTo :: Num a => Rect2D a -> Point2 a -> Rect2D a
- rectFromPoint :: Num a => Point2 a -> Rect2D a
- rectCentralPoint :: Rect2D Int -> Point2 Int
- rectCentralRect :: Rect2D Int -> Size -> Rect2D Int
- rectStretchTo :: Num a => Rect2D a -> Size2D a -> Rect2D a
- rectCentralPointDouble :: Fractional a => Rect2D a -> Point2 a
- rectCentralRectDouble :: Fractional 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]
- rectUnion :: (Num a, Ord a) => Rect2D a -> Rect2D a -> Rect2D a
- rectOverlap :: (Num a, Ord a) => Rect2D a -> Rect2D a -> Rect2D a
- rectUnions :: (Num a, Ord a) => [Rect2D a] -> Rect2D a
- unitIO :: IO a -> IO ()
- bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c
- bracket_ :: IO a -> IO b -> IO c -> IO c
- finally :: IO a -> IO b -> IO a
- finalize :: IO b -> IO a -> IO a
- when :: Bool -> IO () -> IO ()
Basic Types
Objects
(#) :: obj -> (obj -> a) -> a
Reverse application, i.e. x # f
= f x
.
Useful for an object oriented style of programming.
(frame # frameSetTitle) "hi"
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
wxWindows, 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
includeing 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.WXH.WxcClasses 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
wxWindows library are automatically deleted by the library. The only objects
that should be used with care are resources as bitmaps, fonts and brushes.
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
When creating a new window you may specify idAny
to let wxWindows
assign an unused identifier to it automatically. Furthermore, it can be
used in an event connection to handle events for any identifier.
Mutable variables
A mutable variable. Use this instead of MVar
s or IORef
s to accomodate for
future expansions with possible concurrency.
varUpdate :: Var a -> (a -> a) -> IO a
Update the value of a mutable variable and return the old value.
Bits
class Eq b => BitMask b whereSource
Data types that can be represented through a bit mask. Only the assocBitMask
method
is required for a new instance.
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.
Convert to a bitmask
fromBitMask :: Int -> bSource
Convert from a bitmask
setBitMask :: b -> Int -> IntSource
Set the correct bits corresponding to a constructor in a mask.
Booleans
Misc.
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.
colorGreen :: Num a => Color -> a
Returns a green color component
mediumgrey :: Color
System colors
data SystemColor
System Colors.
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. |
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 wxWindows FontStyle
is renamed to FontShape
.
FontStyle | |
|
data FontFamily
Standard font families.
FontDefault | A system default font. |
FontDecorative | Decorative font. |
FontRoman | Formal serif font. |
FontScript | Hand writing font. |
FontSwiss | Sans-serif font. |
FontModern | Fixed pitch font. |
Default 10pt font.
Default 10pt italic.
Brush
data BrushKind
Brush kind.
BrushTransparent | No filling |
BrushSolid | Solid color |
BrushHatch | Hatch pattern |
BrushStipple | Bitmap pattern (on win95 only 8x8 bitmaps are supported) |
|
data HatchStyle
Hatch style.
HatchBDiagonal | Backward diagonal |
HatchCrossDiag | Crossed diagonal |
HatchFDiagonal | Forward diagonal |
HatchCross | Crossed orthogonal |
HatchHorizontal | Horizontal |
HatchVertical | Vertical |
Default brush (transparent, black).
brushTransparent :: BrushStyle
A transparent brush.
Pen
data PenKind
Pen kinds.
PenTransparent | No edge. |
PenSolid | |
PenDash | |
PenHatch | |
| |
PenStipple |
|
|
data JoinStyle
Join style.
Default pen (PenStyle PenSolid black 1 CapRound JoinRound
)
penColored :: Color -> Int -> PenStyle
A solid pen with a certain color and width.
A transparent pen.
Geometrical types
Points
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.
pointFromVec :: Num a => Vector -> Point2 a
pointFromSize :: Num a => Size -> Point2 a
pointNull :: Num a => Point2 a
A null
point is not a legal point (x and y are -1) and can be used for some
wxWindows functions to select a default point.
pointMoveBySize :: Num a => Point2 a -> Size2D a -> Point2 a
pointScale :: Num a => Point2 a -> a -> Point2 a
Sizes
A Size
has a width and height.
sizeFromPoint :: Num a => Point2 a -> Size2D a
sizeFromVec :: Num a => Vector2 a -> Size2D a
A null
size is not a legal size (width and height are -1) and can be used for some
wxWindows 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.
Vectors
A vector with an x and y delta.
vecFromPoint :: Num a => Point2 a -> Vector2 a
vecFromSize :: Size -> Vector
A null
vector has a delta x and y of -1 and can be used for some
wxWindows functions to select a default vector.
vecOrtogonal :: Num a => Vector2 a -> Vector2 a
vecBetween :: Num a => Point2 a -> Point2 a -> Vector2 a
vecLengthDouble :: Vector2 Double -> Double
Rectangles
A rectangle is defined by the left x coordinate, the top y coordinate, the width and the height.
Rect | |
|
rectTopLeft :: Num a => Rect2D a -> Point2 a
rectTopRight :: Num a => Rect2D a -> Point2 a
rectBottomLeft :: Num a => Rect2D a -> Point2 a
rectBottomRight :: Num a => Rect2D a -> Point2 a
rectBottom :: 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).
An null
rectangle is not a valid rectangle (Rect -1 -1 -1 -1
) but can
used for some wxWindows functions to select a default rectangle. (i.e. frameCreate
).
rectIsEmpty :: Num a => Rect2D a -> Bool
rectMoveTo :: Num a => Rect2D a -> Point2 a -> Rect2D a
rectFromPoint :: Num a => Point2 a -> Rect2D a
rectCentralPoint :: Rect2D Int -> Point2 Int
rectStretchTo :: Num a => Rect2D a -> Size2D a -> Rect2D a
rectCentralPointDouble :: Fractional a => Rect2D a -> Point2 a
rectCentralRectDouble :: Fractional a => Rect2D a -> Size2D a -> Rect2D a
rectsDiff :: (Num a, Ord a) => Rect2D a -> Rect2D a -> [Rect2D a]
A list with rectangles that constitute the difference between two rectangles.
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
:: 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.
:: 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.
Run some computation afterwards, even if an exception occurs.
Run some computation afterwards, even if an exception occurs. Equals finally
but
with the arguments swapped.