wxcore-0.12.1.4: wxHaskell core

Portabilityportable
Stabilityprovisional
Maintainerwxhaskell-devel@lists.sourceforge.net

Graphics.UI.WXCore.Types

Contents

Description

Basic types and operations.

Synopsis

Objects

(#) :: obj -> (obj -> a) -> aSource

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

 (frame # frameSetTitle) "hi"

data Object a Source

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.

Instances

Eq (Object a) 
Ord (Object a) 
Show (Object a) 

objectNull :: Object aSource

A null object. Use with care.

objectIsNull :: Object a -> BoolSource

Test for null object.

objectCast :: Object a -> Object bSource

Cast an object to another type. Use with care.

objectIsManaged :: Object a -> BoolSource

Is this a managed object.

objectDelete :: WxObject a -> IO ()Source

Delete a wxObject, works for managed and unmanaged objects.

withObjectPtr :: Object a -> (Ptr a -> IO b) -> IO bSource

Do something with the object pointer.

withObjectRef :: String -> Object a -> (Ptr a -> IO b) -> IO bSource

Extract the object pointer and raise an exception if NULL. Otherwise continue with the valid pointer.

withObjectResult :: IO (Ptr a) -> IO (Object a)Source

Return an unmanaged object.

withManagedObjectResult :: IO (Ptr (TWxObject a)) -> IO (WxObject a)Source

Create a managed object that will be deleted using |wxObject_SafeDelete|.

objectFinalize :: Object a -> IO ()Source

Finalize a managed object manually. (no effect on unmanaged objects)

objectNoFinalize :: Object a -> IO ()Source

Remove the finalizer on a managed object. (no effect on unmanaged objects)

objectFromPtr :: Ptr a -> Object aSource

Create an unmanaged object.

managedObjectFromPtr :: Ptr (TWxObject a) -> IO (WxObject a)Source

Create a managed object that will be deleted using |wxObject_SafeDelete|.

Identifiers

type Id = IntSource

An Id is used to identify objects during event handling.

idAny :: IdSource

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.

idCreate :: IO IdSource

Create a new unique identifier.

Bits

(.+.) :: Int -> Int -> IntSource

Bitwise or of two bit masks.

(.-.) :: Int -> BitFlag -> IntSource

Unset certain bits in a bitmask.

bits :: [Int] -> IntSource

Bitwise or of a list of bit masks.

bitsSet :: Int -> Int -> BoolSource

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

Control

unitIO :: IO a -> IO ()Source

Ignore the result of an IO action.

bracketSource

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_Source

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.

finallySource

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.

finalizeSource

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 ()Source

Perform an action when a test succeeds.

Variables

type Var a = TVar aSource

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

varCreate :: a -> IO (Var a)Source

Create a fresh mutable variable.

varGet :: Var a -> IO aSource

Get the value of a mutable variable.

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

Set the value of a mutable variable.

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

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

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

Swap the value of a mutable variable.

Misc.

type Style = IntSource

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

type EventId = IntSource

An EventId is identifies specific events.

data TreeItem Source

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

treeItemInvalid :: TreeItemSource

Invalid tree item.

treeItemIsOk :: TreeItem -> BoolSource

Is a tree item ok? (i.e. not invalid).

Basic types

Booleans

Colors

data Color Source

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.

rgb :: Integral a => a -> a -> a -> ColorSource

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

colorRGB :: Integral a => a -> a -> a -> ColorSource

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

colorRed :: Num a => Color -> aSource

Returns a red color component

colorGreen :: Num a => Color -> aSource

Returns a green color component

colorBlue :: Num a => Color -> aSource

Returns a blue color component

intFromColor :: Color -> IntSource

Return an Int where the three least significant bytes contain the red, green, and blue component of a color.

colorFromInt :: Int -> ColorSource

Set the color according to an rgb integer. (see rgbIntFromColor).

colorIsOk :: Color -> BoolSource

Check of a color is valid (Colour::IsOk)

colorOk :: Color -> BoolSource

deprecated: use colorIsOk instead.

System colors

data SystemColor Source

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 -> ColorSource

Convert a system color to a color.

Points

data Num a => Point2 a Source

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

Typeable1 Point2 
Num a => Eq (Point2 a) 
(Num a, Ord a) => Ord (Point2 a) 
(Num a, Read a) => Read (Point2 a) 
Num a => Show (Point2 a) 
Ix (Point2 Int) 

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

Construct a point.

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

Shorter function to construct a point.

pointZero :: Num a => Point2 aSource

Point at the origin.

pointNull :: Num a => Point2 aSource

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.

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

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

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

Sizes

data Num a => Size2D a Source

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

Typeable1 Size2D 
Num a => Eq (Size2D a) 
Num a => Show (Size2D a) 

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

Short function to construct a size

sizeNull :: Num a => Size2D aSource

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 -> BoolSource

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

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

The minimum of two sizes.

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

The maximum of two sizes.

Vectors

data Num a => Vector2 a Source

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

Typeable1 Vector2 
Num a => Eq (Vector2 a) 
(Num a, Read a) => Read (Vector2 a) 
Num a => Show (Vector2 a) 

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

Construct a vector.

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

Short function to construct a vector.

vecZero :: Num a => Vector2 aSource

A zero vector

vecNull :: Num a => Vector2 aSource

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

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

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

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

Rectangles

data Num a => Rect2D a Source

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

Typeable1 Rect2D 
Num a => Eq (Rect2D a) 
(Num a, Read a) => Read (Rect2D a) 
Num a => Show (Rect2D a) 

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

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

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

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

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

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

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

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

rectZero :: Num a => Rect2D aSource

An empty rectangle at (0,0).

rectNull :: Num a => Rect2D aSource

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).

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

Get the size of a rectangle.

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

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

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

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

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

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

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

The intersection between two rectangles.

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