wxcore-0.92.0.0: wxHaskell core

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

Graphics.UI.WXCore.WxcTypes

Contents

Description

Basic types and marshalling code for the wxWidgets C library.

Synopsis

Object types

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

Eq (Object a) 
Ord (Object a) 
Show (Object a) 
Widget (Window a) 

objectNull :: Object a Source

A null object. Use with care.

objectIsNull :: Object a -> Bool Source

Test for null object.

objectCast :: Object a -> Object b Source

Cast an object to another type. Use with care.

objectIsManaged :: Object a -> Bool Source

Is this a managed object?

objectDelete :: WxObject a -> IO () Source

Delete a wxObject, works for managed and unmanaged objects.

objectFromPtr :: Ptr a -> Object a Source

Create an unmanaged object.

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

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

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

Do something with the object pointer.

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

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

Type synonyms

type Id = Int Source

An Id is used to identify objects during event handling.

type Style = Int Source

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

type EventId = Int Source

An EventId is identifies specific events.

Basic types

fromBool :: Num a => Bool -> a

Convert a Haskell Bool to its numeric representation

toBool :: (Eq a, Num a) => a -> Bool

Convert a Boolean in numeric representation to a Haskell value

Point

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

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

Construct a point.

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

Shorter function to construct a point.

pointZero :: Num a => Point2 a Source

Point at the origin.

pointNull :: Num a => Point2 a Source

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.

Size

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

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

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

Short function to construct a size

sizeNull :: Num a => Size2D a Source

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.

Vector

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

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

Construct a vector.

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

Short function to construct a vector.

vecZero :: Num a => Vector2 a Source

A zero vector

vecNull :: Num a => Vector2 a Source

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

Rectangle

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

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

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

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

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

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

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

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

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

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

rectZero :: Num a => Rect2D a Source

An empty rectangle at (0,0).

rectNull :: Num a => Rect2D a Source

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 Source

Get the size of a rectangle.

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

Color

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

Constructors

Color Word 

Instances

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

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

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

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

rgba :: Integral a => a -> a -> a -> a -> Color Source

Create a color from a red/green/blue/alpha quadruple.

colorRGBA :: Integral a => a -> a -> a -> a -> Color Source

Create a color from a red/green/blue/alpha quadruple.

colorRed :: Num a => Color -> a Source

Returns a red color component

colorGreen :: Num a => Color -> a Source

Returns a green color component

colorBlue :: Num a => Color -> a Source

Returns a blue color component

colorAlpha :: Num a => Color -> a Source

Returns a alpha channel component

intFromColor :: Color -> Int Source

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

colorFromInt :: Int -> Color Source

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

fromColor :: Num a => Color -> a Source

Return an Num class's numeric representation where the three least significant the red, green, and blue component of a color.

toColor :: Integral a => a -> Color Source

Set the color according to Integral class's numeric representation. (see rgbaIntFromColor).

colorOk :: Color -> Bool Source

Deprecated: Use colorIsOk instead

deprecated: use colorIsOk instead.

colorIsOk :: Color -> Bool Source

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

Marshalling

Basic types

withCPoint :: Point2 Int -> (CInt -> CInt -> IO a) -> IO a Source

withCSize :: Size -> (CInt -> CInt -> IO a) -> IO a Source

withCVector :: Vector -> (CInt -> CInt -> IO a) -> IO a Source

withWxRectPtr :: Rect -> (Ptr (TWxRect r) -> IO a) -> IO a Source

withCRect :: Rect -> (CInt -> CInt -> CInt -> CInt -> IO a) -> IO a Source

withArray :: Storable a => [a] -> (Ptr a -> IO b) -> IO b

Temporarily store a list of storable values in memory (like with, but for multiple elements).

withArrayString :: [String] -> (CInt -> Ptr CString -> IO a) -> IO a Source

withArrayInt :: [Int] -> (CInt -> Ptr CInt -> IO a) -> IO a Source

withArrayIntPtr :: [IntPtr] -> (CInt -> Ptr CIntPtr -> IO a) -> IO a Source

withArrayObject :: [Ptr a] -> (CInt -> Ptr (Ptr a) -> IO b) -> IO b Source

Managed object types

data TreeItem Source

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

treeItemInvalid :: TreeItem Source

Invalid tree item.

treeItemIsOk :: TreeItem -> Bool Source

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

withStringRef :: String -> String -> (Ptr (TWxString s) -> IO a) -> IO a Source

withStringPtr :: String -> (Ptr (TWxString s) -> IO a) -> IO a Source

withColourRef :: String -> Color -> (Ptr (TColour a) -> IO b) -> IO b Source

withColourPtr :: Color -> (Ptr (TColour a) -> IO b) -> IO b Source

withRefBitmap :: (Ptr (TBitmap a) -> IO ()) -> IO (Bitmap a) Source

withRefCursor :: (Ptr (TCursor a) -> IO ()) -> IO (Cursor a) Source

withRefIcon :: (Ptr (TIcon a) -> IO ()) -> IO (Icon a) Source

withRefPen :: (Ptr (TPen a) -> IO ()) -> IO (Pen a) Source

withRefBrush :: (Ptr (TBrush a) -> IO ()) -> IO (Brush a) Source

withRefFont :: (Ptr (TFont a) -> IO ()) -> IO (Font a) Source

withRefImage :: (Ptr (TImage a) -> IO ()) -> IO (Image a) Source

Primitive types

CString

type CString = Ptr CChar

A C string is a reference to an array of C characters terminated by NUL.

withCString :: String -> (CString -> IO a) -> IO a

Marshal a Haskell string into a NUL terminated C string using temporary storage.

  • the Haskell string may not contain any NUL characters
  • the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.

type CWString = Ptr CWchar

A C wide string is a reference to an array of C wide characters terminated by NUL.

withCWString :: String -> (CWString -> IO a) -> IO a

Marshal a Haskell string into a NUL terminated C wide string using temporary storage.

  • the Haskell string may not contain any NUL characters
  • the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.

ByteString

CInt

newtype CInt :: *

Haskell type representing the C int type.

Constructors

CInt Int32 

IntPtr

data IntPtr :: *

A signed integral type that can be losslessly converted to and from Ptr. This type is also compatible with the C99 type intptr_t, and can be marshalled to and from that type safely.

CIntPtr

Word

data Word :: *

A Word is an unsigned integral type, with the same size as Int.

8 bit Word

64 bit Integer

CDouble

CChar

newtype CChar :: *

Haskell type representing the C char type.

Constructors

CChar Int8 

newtype CWchar :: *

Haskell type representing the C wchar_t type.

Constructors

CWchar Int32 

toCWchar :: Num a => Char -> a Source

CBool

Pointers

data Ptr a :: * -> *

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

The type a will often be an instance of class Storable which provides the marshalling operations. However this is not essential, and you can provide your own operations to access the pointer. For example you might write small foreign functions to get or set the fields of a C struct.

Instances

IArray UArray (Ptr a) 
Eq (Ptr a) 
Ord (Ptr a) 
Show (Ptr a) 
Storable (Ptr a) 
MArray (STUArray s) (Ptr a) (ST s) 
Typeable (* -> *) Ptr 

ptrNull :: Ptr a Source

Null pointer, use with care.

ptrIsNull :: Ptr a -> Bool Source

Test for null.

ptrCast :: Ptr a -> Ptr b Source

Cast a pointer type, use with care.

data ForeignPtr a :: * -> *

The type ForeignPtr represents references to objects that are maintained in a foreign language, i.e., that are not part of the data structures usually managed by the Haskell storage manager. The essential difference between ForeignPtrs and vanilla memory references of type Ptr a is that the former may be associated with finalizers. A finalizer is a routine that is invoked when the Haskell storage manager detects that - within the Haskell heap and stack - there are no more references left that are pointing to the ForeignPtr. Typically, the finalizer will, then, invoke routines in the foreign language that free the resources bound by the foreign object.

The ForeignPtr is parameterised in the same way as Ptr. The type argument of ForeignPtr should normally be an instance of class Storable.

Instances

data FunPtr a :: * -> *

A value of type FunPtr a is a pointer to a function callable from foreign code. The type a will normally be a foreign type, a function type with zero or more arguments where

A value of type FunPtr a may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import like

foreign import ccall "stdlib.h &free"
  p_free :: FunPtr (Ptr a -> IO ())

or a pointer to a Haskell function created using a wrapper stub declared to produce a FunPtr of the correct type. For example:

type Compare = Int -> Int -> Bool
foreign import ccall "wrapper"
  mkCompare :: Compare -> IO (FunPtr Compare)

Calls to wrapper stubs like mkCompare allocate storage, which should be released with freeHaskellFunPtr when no longer required.

To convert FunPtr values to corresponding Haskell functions, one can define a dynamic stub for the specific foreign type, e.g.

type IntFunction = CInt -> IO ()
foreign import ccall "dynamic" 
  mkFun :: FunPtr IntFunction -> IntFunction

Instances

IArray UArray (FunPtr a) 
Eq (FunPtr a) 
Ord (FunPtr a) 
Show (FunPtr a) 
Storable (FunPtr a) 
MArray (STUArray s) (FunPtr a) (ST s) 
Typeable (* -> *) FunPtr