| Portability | portable | 
|---|---|
| Stability | provisional | 
| Maintainer | wxhaskell-devel@lists.sourceforge.net | 
Graphics.UI.WXCore.WxcTypes
Contents
Description
Basic types and marshaling code for the wxWindows C library.
- data Object a
- objectNull :: Object a
- objectIsNull :: Object a -> Bool
- objectCast :: Object a -> Object b
- objectIsManaged :: Object a -> Bool
- objectDelete :: WxObject a -> IO ()
- objectFromPtr :: Ptr a -> Object a
- managedObjectFromPtr :: Ptr (TWxObject a) -> IO (WxObject a)
- withObjectPtr :: Object a -> (Ptr a -> IO b) -> IO b
- withObjectRef :: String -> Object a -> (Ptr a -> IO b) -> IO b
- withObjectResult :: IO (Ptr a) -> IO (Object a)
- withManagedObjectResult :: IO (Ptr (TWxObject a)) -> IO (WxObject a)
- objectFinalize :: Object a -> IO ()
- objectNoFinalize :: Object a -> IO ()
- type Id = Int
- type Style = Int
- type EventId = Int
- fromBool :: Num a => Bool -> a
- toBool :: Num a => a -> Bool
- 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
- 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
- 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
- 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
- newtype Color = Color Word
- rgb :: Int -> Int -> Int -> Color
- colorRGB :: Int -> Int -> Int -> Color
- rgba :: Int -> Int -> Int -> Int -> Color
- colorRGBA :: Int -> Int -> Int -> Int -> Color
- colorRed :: Color -> Int
- colorGreen :: Color -> Int
- colorBlue :: Color -> Int
- colorAlpha :: Color -> Int
- intFromColor :: Color -> Int
- colorFromInt :: Int -> Color
- wordFromColor :: Color -> Word
- colorFromWord :: Word -> Color
- colorOk :: Color -> Bool
- withPointResult :: (Ptr CInt -> Ptr CInt -> IO ()) -> IO (Point2 Int)
- toCIntPointX :: Point2 Int -> CInt
- toCIntPointY :: Point2 Int -> CInt
- fromCPoint :: CInt -> CInt -> Point2 Int
- withCPoint :: Point2 Int -> (CInt -> CInt -> IO a) -> IO a
- withPointDoubleResult :: (Ptr CDouble -> Ptr CDouble -> IO ()) -> IO (Point2 Double)
- toCDoublePointX :: Point2 Double -> CDouble
- toCDoublePointY :: Point2 Double -> CDouble
- fromCPointDouble :: CDouble -> CDouble -> Point2 Double
- withCPointDouble :: Point2 Double -> (CDouble -> CDouble -> IO a) -> IO a
- withSizeResult :: (Ptr CInt -> Ptr CInt -> IO ()) -> IO Size
- toCIntSizeW :: Size -> CInt
- toCIntSizeH :: Size -> CInt
- fromCSize :: CInt -> CInt -> Size
- withCSize :: Size -> (CInt -> CInt -> IO a) -> IO a
- withSizeDoubleResult :: (Ptr CDouble -> Ptr CDouble -> IO ()) -> IO (Size2D Double)
- toCDoubleSizeW :: Size2D Double -> CDouble
- toCDoubleSizeH :: Size2D Double -> CDouble
- fromCSizeDouble :: CDouble -> CDouble -> Size2D Double
- withCSizeDouble :: Size2D Double -> (CDouble -> CDouble -> IO a) -> IO a
- withVectorResult :: (Ptr CInt -> Ptr CInt -> IO ()) -> IO Vector
- toCIntVectorX :: Vector -> CInt
- toCIntVectorY :: Vector -> CInt
- fromCVector :: CInt -> CInt -> Vector
- withCVector :: Vector -> (CInt -> CInt -> IO a) -> IO a
- withVectorDoubleResult :: (Ptr CDouble -> Ptr CDouble -> IO ()) -> IO (Vector2 Double)
- toCDoubleVectorX :: Vector2 Double -> CDouble
- toCDoubleVectorY :: Vector2 Double -> CDouble
- fromCVectorDouble :: CDouble -> CDouble -> Vector2 Double
- withCVectorDouble :: Vector2 Double -> (CDouble -> CDouble -> IO a) -> IO a
- withRectResult :: (Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()) -> IO Rect
- toCIntRectX :: Rect -> CInt
- toCIntRectY :: Rect -> CInt
- toCIntRectW :: Rect -> CInt
- toCIntRectH :: Rect -> CInt
- fromCRect :: CInt -> CInt -> CInt -> CInt -> Rect
- withCRect :: Rect -> (CInt -> CInt -> CInt -> CInt -> IO a) -> IO a
- withRectDoubleResult :: (Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()) -> IO (Rect2D Double)
- toCDoubleRectX :: Rect2D Double -> CDouble
- toCDoubleRectY :: Rect2D Double -> CDouble
- toCDoubleRectW :: Rect2D Double -> CDouble
- toCDoubleRectH :: Rect2D Double -> CDouble
- fromCRectDouble :: CDouble -> CDouble -> CDouble -> CDouble -> Rect2D Double
- withCRectDouble :: Rect2D Double -> (CDouble -> CDouble -> CDouble -> CDouble -> IO a) -> IO a
- withArray :: Storable a => [a] -> (Ptr a -> IO b) -> IO b
- withArrayString :: [String] -> (CInt -> Ptr CString -> IO a) -> IO a
- withArrayWString :: [String] -> (CInt -> Ptr CWString -> IO a) -> IO a
- withArrayInt :: [Int] -> (CInt -> Ptr CInt -> IO a) -> IO a
- withArrayObject :: [Ptr a] -> (CInt -> Ptr (Ptr a) -> IO b) -> IO b
- withArrayIntResult :: (Ptr CInt -> IO CInt) -> IO [Int]
- withArrayStringResult :: (Ptr (Ptr CChar) -> IO CInt) -> IO [String]
- withArrayWStringResult :: (Ptr (Ptr CWchar) -> IO CInt) -> IO [String]
- withArrayObjectResult :: (Ptr (Ptr a) -> IO CInt) -> IO [Object a]
- colourFromColor :: Color -> IO (Colour ())
- colorFromColour :: Colour a -> IO Color
- colourCreate :: IO (Ptr (TColour a))
- colourSafeDelete :: Ptr (TColour a) -> IO ()
- toWord8ColorRed :: Color -> Word8
- toWord8ColorGreen :: Color -> Word8
- toWord8ColorBlue :: Color -> Word8
- toWord8ColorAlpha :: Color -> Word8
- data TreeItem
- treeItemInvalid :: TreeItem
- treeItemIsOk :: TreeItem -> Bool
- treeItemFromInt :: Int -> TreeItem
- withRefTreeItemId :: (Ptr (TTreeItemId ()) -> IO ()) -> IO TreeItem
- withTreeItemIdPtr :: TreeItem -> (Ptr (TTreeItemId a) -> IO b) -> IO b
- withTreeItemIdRef :: String -> TreeItem -> (Ptr (TTreeItemId a) -> IO b) -> IO b
- withManagedTreeItemIdResult :: IO (Ptr (TTreeItemId a)) -> IO TreeItem
- withStringRef :: String -> String -> (Ptr (TWxString s) -> IO a) -> IO a
- withStringPtr :: String -> (Ptr (TWxString s) -> IO a) -> IO a
- withManagedStringResult :: IO (Ptr (TWxString a)) -> IO String
- withRefColour :: (Ptr (TColour a) -> IO ()) -> IO Color
- withColourRef :: String -> Color -> (Ptr (TColour a) -> IO b) -> IO b
- withColourPtr :: Color -> (Ptr (TColour a) -> IO b) -> IO b
- withManagedColourResult :: IO (Ptr (TColour a)) -> IO Color
- withRefBitmap :: (Ptr (TBitmap a) -> IO ()) -> IO (Bitmap a)
- withManagedBitmapResult :: IO (Ptr (TBitmap a)) -> IO (Bitmap a)
- withRefCursor :: (Ptr (TCursor a) -> IO ()) -> IO (Cursor a)
- withManagedCursorResult :: IO (Ptr (TCursor a)) -> IO (Cursor a)
- withRefIcon :: (Ptr (TIcon a) -> IO ()) -> IO (Icon a)
- withManagedIconResult :: IO (Ptr (TIcon a)) -> IO (Icon a)
- withRefPen :: (Ptr (TPen a) -> IO ()) -> IO (Pen a)
- withManagedPenResult :: IO (Ptr (TPen a)) -> IO (Pen a)
- withRefBrush :: (Ptr (TBrush a) -> IO ()) -> IO (Brush a)
- withManagedBrushResult :: IO (Ptr (TBrush a)) -> IO (Brush a)
- withRefFont :: (Ptr (TFont a) -> IO ()) -> IO (Font a)
- withManagedFontResult :: IO (Ptr (TFont a)) -> IO (Font a)
- withRefImage :: (Ptr (TImage a) -> IO ()) -> IO (Image a)
- withRefListItem :: (Ptr (TListItem a) -> IO ()) -> IO (ListItem a)
- withRefFontData :: (Ptr (TFontData a) -> IO ()) -> IO (FontData a)
- withRefPrintData :: (Ptr (TPrintData a) -> IO ()) -> IO (PrintData a)
- withRefPageSetupDialogData :: (Ptr (TPageSetupDialogData a) -> IO ()) -> IO (PageSetupDialogData a)
- withRefPrintDialogData :: (Ptr (TPrintDialogData a) -> IO ()) -> IO (PrintDialogData a)
- withRefDateTime :: (Ptr (TDateTime a) -> IO ()) -> IO (DateTime a)
- withManagedDateTimeResult :: IO (Ptr (TDateTime a)) -> IO (DateTime a)
- withRefGridCellCoordsArray :: (Ptr (TGridCellCoordsArray a) -> IO ()) -> IO (GridCellCoordsArray a)
- withManagedGridCellCoordsArrayResult :: IO (Ptr (TGridCellCoordsArray a)) -> IO (GridCellCoordsArray a)
- type CString = Ptr CChar
- withCString :: String -> (CString -> IO a) -> IO a
- withStringResult :: (Ptr CChar -> IO CInt) -> IO String
- type CWString = Ptr CWchar
- withCWString :: String -> (CWString -> IO a) -> IO a
- withWStringResult :: (Ptr CWchar -> IO CInt) -> IO String
- withByteStringResult :: (Ptr CChar -> IO CInt) -> IO ByteString
- withLazyByteStringResult :: (Ptr CChar -> IO CInt) -> IO ByteString
- data CInt
- toCInt :: Int -> CInt
- fromCInt :: CInt -> Int
- withIntResult :: IO CInt -> IO Int
- data Word
- data Word8
- data Int64
- data CDouble
- toCDouble :: Double -> CDouble
- fromCDouble :: CDouble -> Double
- withDoubleResult :: IO CDouble -> IO Double
- data CChar
- toCChar :: Char -> CChar
- fromCChar :: CChar -> Char
- withCharResult :: (Num a, Integral a) => IO a -> IO Char
- data CWchar
- toCWchar :: Num a => Char -> a
- type CBool = CInt
- toCBool :: Bool -> CBool
- fromCBool :: CBool -> Bool
- withBoolResult :: IO CBool -> IO Bool
- data Ptr a
- ptrNull :: Ptr a
- ptrIsNull :: Ptr a -> Bool
- ptrCast :: Ptr a -> Ptr b
- data ForeignPtr a
- data FunPtr a
- toCFunPtr :: FunPtr a -> Ptr a
Object types
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.
objectFromPtr :: Ptr a -> Object a
Create an unmanaged object.
managedObjectFromPtr :: Ptr (TWxObject a) -> IO (WxObject a)
Create a managed object that will be deleted using |wxObject_SafeDelete|.
withObjectPtr :: Object a -> (Ptr a -> IO b) -> IO b
Do something with the object pointer.
withObjectRef :: String -> Object a -> (Ptr a -> IO b) -> IO b
Extract the object pointer and raise an exception if NULL.
 Otherwise continue with the valid pointer.
withObjectResult :: IO (Ptr a) -> IO (Object a)
Return an unmanaged object.
withManagedObjectResult :: IO (Ptr (TWxObject a)) -> IO (WxObject a)
Create a managed object that will be deleted using |wxObject_SafeDelete|.
objectFinalize :: Object a -> IO ()
Finalize a managed object manually. (no effect on unmanaged objects)
objectNoFinalize :: Object a -> IO ()
Remove the finalizer on a managed object. (no effect on unmanaged objects)
Type synonyms
type Id = Int
An Id is used to identify objects during event handling.
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.
Basic types
fromBool :: Num a => Bool -> a
toBool :: Num a => a -> Bool
Point
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.
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.
Size
data Num a => Size2D a
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.
Vector
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.
Rectangle
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 
 | |
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
Color
newtype 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 :: Color -> Int
Returns a green color component
colorAlpha :: Color -> Int
Returns a alpha channel component
intFromColor :: Color -> Int
Return an Int where the three least significant bytes contain
 the red, green, and blue component of a color.
colorFromInt :: Int -> Color
Set the color according to an rgb integer. (see rgbIntFromColor).
wordFromColor :: Color -> Word
Return an Int where the three least significant bytes contain
 the red, green, and blue component of a color.
colorFromWord :: Word -> Color
Set the color according to an rgba unsigned integer. (see rgbaIntFromColor).
Marshalling
Basic types
toCIntPointX :: Point2 Int -> CInt
toCIntPointY :: Point2 Int -> CInt
fromCPoint :: CInt -> CInt -> Point2 Int
withCPoint :: Point2 Int -> (CInt -> CInt -> IO a) -> IO a
toCDoublePointX :: Point2 Double -> CDouble
toCDoublePointY :: Point2 Double -> CDouble
fromCPointDouble :: CDouble -> CDouble -> Point2 Double
withCPointDouble :: Point2 Double -> (CDouble -> CDouble -> IO a) -> IO a
toCIntSizeW :: Size -> CInt
toCIntSizeH :: Size -> CInt
toCDoubleSizeW :: Size2D Double -> CDouble
toCDoubleSizeH :: Size2D Double -> CDouble
fromCSizeDouble :: CDouble -> CDouble -> Size2D Double
withCSizeDouble :: Size2D Double -> (CDouble -> CDouble -> IO a) -> IO a
toCIntVectorX :: Vector -> CInt
toCIntVectorY :: Vector -> CInt
fromCVector :: CInt -> CInt -> Vector
withCVector :: Vector -> (CInt -> CInt -> IO a) -> IO a
toCDoubleVectorX :: Vector2 Double -> CDouble
toCDoubleVectorY :: Vector2 Double -> CDouble
fromCVectorDouble :: CDouble -> CDouble -> Vector2 Double
withCVectorDouble :: Vector2 Double -> (CDouble -> CDouble -> IO a) -> IO a
toCIntRectX :: Rect -> CInt
toCIntRectY :: Rect -> CInt
toCIntRectW :: Rect -> CInt
toCIntRectH :: Rect -> CInt
withRectDoubleResult :: (Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()) -> IO (Rect2D Double)
toCDoubleRectX :: Rect2D Double -> CDouble
toCDoubleRectY :: Rect2D Double -> CDouble
toCDoubleRectW :: Rect2D Double -> CDouble
toCDoubleRectH :: Rect2D Double -> CDouble
withArrayString :: [String] -> (CInt -> Ptr CString -> IO a) -> IO a
withArrayWString :: [String] -> (CInt -> Ptr CWString -> IO a) -> IO a
withArrayInt :: [Int] -> (CInt -> Ptr CInt -> IO a) -> IO a
withArrayObject :: [Ptr a] -> (CInt -> Ptr (Ptr a) -> IO b) -> IO b
withArrayIntResult :: (Ptr CInt -> IO CInt) -> IO [Int]
withArrayStringResult :: (Ptr (Ptr CChar) -> IO CInt) -> IO [String]
withArrayWStringResult :: (Ptr (Ptr CWchar) -> IO CInt) -> IO [String]
withArrayObjectResult :: (Ptr (Ptr a) -> IO CInt) -> IO [Object a]
colourFromColor :: Color -> IO (Colour ())
colorFromColour :: Colour a -> IO Color
colourCreate :: IO (Ptr (TColour a))
colourSafeDelete :: Ptr (TColour a) -> IO ()
toWord8ColorRed :: Color -> Word8
toWord8ColorGreen :: Color -> Word8
toWord8ColorBlue :: Color -> Word8
toWord8ColorAlpha :: Color -> Word8
Managed object types
data TreeItem
Identifies tree items. Note: Replaces the TreeItemId object and takes automatically
 care of allocation issues.
Invalid tree item.
treeItemIsOk :: TreeItem -> Bool
Is a tree item ok? (i.e. not invalid).
treeItemFromInt :: Int -> TreeItem
withRefTreeItemId :: (Ptr (TTreeItemId ()) -> IO ()) -> IO TreeItem
withTreeItemIdPtr :: TreeItem -> (Ptr (TTreeItemId a) -> IO b) -> IO b
withTreeItemIdRef :: String -> TreeItem -> (Ptr (TTreeItemId a) -> IO b) -> IO b
withManagedTreeItemIdResult :: IO (Ptr (TTreeItemId a)) -> IO TreeItem
withStringRef :: String -> String -> (Ptr (TWxString s) -> IO a) -> IO a
withStringPtr :: String -> (Ptr (TWxString s) -> IO a) -> IO a
withManagedStringResult :: IO (Ptr (TWxString a)) -> IO String
withRefColour :: (Ptr (TColour a) -> IO ()) -> IO Color
withColourRef :: String -> Color -> (Ptr (TColour a) -> IO b) -> IO b
withColourPtr :: Color -> (Ptr (TColour a) -> IO b) -> IO b
withManagedColourResult :: IO (Ptr (TColour a)) -> IO Color
withRefBitmap :: (Ptr (TBitmap a) -> IO ()) -> IO (Bitmap a)
withManagedBitmapResult :: IO (Ptr (TBitmap a)) -> IO (Bitmap a)
withRefCursor :: (Ptr (TCursor a) -> IO ()) -> IO (Cursor a)
withManagedCursorResult :: IO (Ptr (TCursor a)) -> IO (Cursor a)
withRefIcon :: (Ptr (TIcon a) -> IO ()) -> IO (Icon a)
withManagedIconResult :: IO (Ptr (TIcon a)) -> IO (Icon a)
withRefPen :: (Ptr (TPen a) -> IO ()) -> IO (Pen a)
withManagedPenResult :: IO (Ptr (TPen a)) -> IO (Pen a)
withRefBrush :: (Ptr (TBrush a) -> IO ()) -> IO (Brush a)
withManagedBrushResult :: IO (Ptr (TBrush a)) -> IO (Brush a)
withRefFont :: (Ptr (TFont a) -> IO ()) -> IO (Font a)
withManagedFontResult :: IO (Ptr (TFont a)) -> IO (Font a)
withRefImage :: (Ptr (TImage a) -> IO ()) -> IO (Image a)
withRefListItem :: (Ptr (TListItem a) -> IO ()) -> IO (ListItem a)
withRefFontData :: (Ptr (TFontData a) -> IO ()) -> IO (FontData a)
withRefPrintData :: (Ptr (TPrintData a) -> IO ()) -> IO (PrintData a)
withRefPageSetupDialogData :: (Ptr (TPageSetupDialogData a) -> IO ()) -> IO (PageSetupDialogData a)
withRefPrintDialogData :: (Ptr (TPrintDialogData a) -> IO ()) -> IO (PrintDialogData a)
withRefDateTime :: (Ptr (TDateTime a) -> IO ()) -> IO (DateTime a)
withManagedDateTimeResult :: IO (Ptr (TDateTime a)) -> IO (DateTime a)
withRefGridCellCoordsArray :: (Ptr (TGridCellCoordsArray a) -> IO ()) -> IO (GridCellCoordsArray a)
withManagedGridCellCoordsArrayResult :: IO (Ptr (TGridCellCoordsArray a)) -> IO (GridCellCoordsArray a)
Primitive types
CString
withCString :: String -> (CString -> IO a) -> IO a
withStringResult :: (Ptr CChar -> IO CInt) -> IO String
withCWString :: String -> (CWString -> IO a) -> IO a
withWStringResult :: (Ptr CWchar -> IO CInt) -> IO String
ByteString
withByteStringResult :: (Ptr CChar -> IO CInt) -> IO ByteString
withLazyByteStringResult :: (Ptr CChar -> IO CInt) -> IO ByteString
CInt
data CInt
withIntResult :: IO CInt -> IO Int
Word
data Word
8 bit Word
data Word8
64 bit Integer
data Int64
CDouble
data CDouble
fromCDouble :: CDouble -> Double
withDoubleResult :: IO CDouble -> IO Double
CChar
data CChar
withCharResult :: (Num a, Integral a) => IO a -> IO Char
data CWchar
toCWchar :: Num a => Char -> a
CBool
withBoolResult :: IO CBool -> IO Bool
Pointers
data Ptr a
data ForeignPtr a
Instances
| Typeable1 ForeignPtr | |
| Eq (ForeignPtr a) | |
| Ord (ForeignPtr a) | |
| Show (ForeignPtr a) | 
data FunPtr a