wxcore-0.12.1.5: wxHaskell core

Portabilityportable
Stabilityprovisional
Maintainerwxhaskell-devel@lists.sourceforge.net

Graphics.UI.WXCore.WxcTypes

Contents

Description

Basic types and marshaling code for the wxWindows 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 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.

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

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)

Type synonyms

type Id = IntSource

An Id is used to identify objects during event handling.

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.

Basic types

fromBool :: Num a => Bool -> a

Convert a Haskell Bool to its numeric representation

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

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.

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

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.

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

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.

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

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.

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 

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.

rgba :: Integral a => a -> a -> a -> a -> ColorSource

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

colorRGBA :: Integral a => a -> a -> a -> a -> ColorSource

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

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

colorAlpha :: Num a => Color -> aSource

Returns a alpha channel 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).

fromColor :: Num a => Color -> aSource

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

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

colorOk :: Color -> BoolSource

deprecated: use colorIsOk instead.

colorIsOk :: Color -> BoolSource

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

Marshalling

Basic types

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

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

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

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

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

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

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

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

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

Managed object types

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

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

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

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

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

withRefFont :: (Ptr (TFont a) -> IO ()) -> IO (Font 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

data CInt

Haskell type representing the C int type.

Word

data Word

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

8 bit Word

64 bit Integer

CDouble

CChar

data CChar

Haskell type representing the C char type.

data CWchar

Haskell type representing the C wchar_t type.

toCWchar :: Num a => Char -> aSource

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 Foreign.Storable.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

Typeable1 Ptr 
IArray UArray (Ptr a) 
Eq (Ptr a) 
Ord (Ptr a) 
Show (Ptr a) 
Storable (Ptr a) 
MArray (STUArray s) (Ptr a) (ST s) 

ptrNull :: Ptr aSource

Null pointer, use with care.

ptrIsNull :: Ptr a -> BoolSource

Test for null.

ptrCast :: Ptr a -> Ptr bSource

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.

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

  • the argument types are marshallable foreign types, i.e. Char, Int, Prelude.Double, Prelude.Float, Bool, Data.Int.Int8, Data.Int.Int16, Data.Int.Int32, Data.Int.Int64, Data.Word.Word8, Data.Word.Word16, Data.Word.Word32, Data.Word.Word64, Ptr a, FunPtr a, Foreign.StablePtr.StablePtr a or a renaming of any of these using newtype.
  • the return type is either a marshallable foreign type or has the form Prelude.IO t where t is a marshallable foreign type or ().

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 Foreign.Ptr.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