wxcore-0.92.3.0: wxHaskell core

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

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

Methods

(==) :: Object a -> Object a -> Bool #

(/=) :: Object a -> Object a -> Bool #

Ord (Object a) Source # 

Methods

compare :: Object a -> Object a -> Ordering #

(<) :: Object a -> Object a -> Bool #

(<=) :: Object a -> Object a -> Bool #

(>) :: Object a -> Object a -> Bool #

(>=) :: Object a -> Object a -> Bool #

max :: Object a -> Object a -> Object a #

min :: Object a -> Object a -> Object a #

Show (Object a) Source # 

Methods

showsPrec :: Int -> Object a -> ShowS #

show :: Object a -> String #

showList :: [Object a] -> ShowS #

Widget (Window a) Source # 

Methods

widget :: Window a -> Layout Source #

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

Methods

(==) :: Point2 a -> Point2 a -> Bool #

(/=) :: Point2 a -> Point2 a -> Bool #

(Num a, Ord a) => Ord (Point2 a) Source # 

Methods

compare :: Point2 a -> Point2 a -> Ordering #

(<) :: Point2 a -> Point2 a -> Bool #

(<=) :: Point2 a -> Point2 a -> Bool #

(>) :: Point2 a -> Point2 a -> Bool #

(>=) :: Point2 a -> Point2 a -> Bool #

max :: Point2 a -> Point2 a -> Point2 a #

min :: Point2 a -> Point2 a -> Point2 a #

(Read a, Num a) => Read (Point2 a) Source # 
(Show a, Num a) => Show (Point2 a) Source # 

Methods

showsPrec :: Int -> Point2 a -> ShowS #

show :: Point2 a -> String #

showList :: [Point2 a] -> ShowS #

Ix (Point2 Int) Source # 

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

Methods

(==) :: Size2D a -> Size2D a -> Bool #

(/=) :: Size2D a -> Size2D a -> Bool #

(Show a, Num a) => Show (Size2D a) Source # 

Methods

showsPrec :: Int -> Size2D a -> ShowS #

show :: Size2D a -> String #

showList :: [Size2D a] -> ShowS #

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

Methods

(==) :: Vector2 a -> Vector2 a -> Bool #

(/=) :: Vector2 a -> Vector2 a -> Bool #

(Read a, Num a) => Read (Vector2 a) Source # 
(Show a, Num a) => Show (Vector2 a) Source # 

Methods

showsPrec :: Int -> Vector2 a -> ShowS #

show :: Vector2 a -> String #

showList :: [Vector2 a] -> ShowS #

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

Instances

(Eq a, Num a) => Eq (Rect2D a) Source # 

Methods

(==) :: Rect2D a -> Rect2D a -> Bool #

(/=) :: Rect2D a -> Rect2D a -> Bool #

(Read a, Num a) => Read (Rect2D a) Source # 
(Show a, Num a) => Show (Rect2D a) Source # 

Methods

showsPrec :: Int -> Rect2D a -> ShowS #

show :: Rect2D a -> String #

showList :: [Rect2D a] -> ShowS #

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.

Color

newtype Color Source #

An abstract data type to define colors.

Constructors

Color Word 

Instances

Eq Color Source # 

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

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

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

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

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 

Instances

Bounded CInt 
Enum CInt 

Methods

succ :: CInt -> CInt #

pred :: CInt -> CInt #

toEnum :: Int -> CInt #

fromEnum :: CInt -> Int #

enumFrom :: CInt -> [CInt] #

enumFromThen :: CInt -> CInt -> [CInt] #

enumFromTo :: CInt -> CInt -> [CInt] #

enumFromThenTo :: CInt -> CInt -> CInt -> [CInt] #

Eq CInt 

Methods

(==) :: CInt -> CInt -> Bool #

(/=) :: CInt -> CInt -> Bool #

Integral CInt 

Methods

quot :: CInt -> CInt -> CInt #

rem :: CInt -> CInt -> CInt #

div :: CInt -> CInt -> CInt #

mod :: CInt -> CInt -> CInt #

quotRem :: CInt -> CInt -> (CInt, CInt) #

divMod :: CInt -> CInt -> (CInt, CInt) #

toInteger :: CInt -> Integer #

Num CInt 

Methods

(+) :: CInt -> CInt -> CInt #

(-) :: CInt -> CInt -> CInt #

(*) :: CInt -> CInt -> CInt #

negate :: CInt -> CInt #

abs :: CInt -> CInt #

signum :: CInt -> CInt #

fromInteger :: Integer -> CInt #

Ord CInt 

Methods

compare :: CInt -> CInt -> Ordering #

(<) :: CInt -> CInt -> Bool #

(<=) :: CInt -> CInt -> Bool #

(>) :: CInt -> CInt -> Bool #

(>=) :: CInt -> CInt -> Bool #

max :: CInt -> CInt -> CInt #

min :: CInt -> CInt -> CInt #

Read CInt 
Real CInt 

Methods

toRational :: CInt -> Rational #

Show CInt 

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Storable CInt 

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

peekElemOff :: Ptr CInt -> Int -> IO CInt #

pokeElemOff :: Ptr CInt -> Int -> CInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CInt #

pokeByteOff :: Ptr b -> Int -> CInt -> IO () #

peek :: Ptr CInt -> IO CInt #

poke :: Ptr CInt -> CInt -> IO () #

Bits CInt 
FiniteBits CInt 

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.

Instances

Bounded IntPtr 
Enum IntPtr 
Eq IntPtr 

Methods

(==) :: IntPtr -> IntPtr -> Bool #

(/=) :: IntPtr -> IntPtr -> Bool #

Integral IntPtr 
Num IntPtr 
Ord IntPtr 
Read IntPtr 
Real IntPtr 
Show IntPtr 
Storable IntPtr 
Bits IntPtr 
FiniteBits IntPtr 

CIntPtr

Word

data Word :: * #

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

Instances

Bounded Word 
Enum Word 

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Eq Word 

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Integral Word 

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Num Word 

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Ord Word 

Methods

compare :: Word -> Word -> Ordering #

(<) :: Word -> Word -> Bool #

(<=) :: Word -> Word -> Bool #

(>) :: Word -> Word -> Bool #

(>=) :: Word -> Word -> Bool #

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Read Word 
Real Word 

Methods

toRational :: Word -> Rational #

Show Word 

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Ix Word 

Methods

range :: (Word, Word) -> [Word] #

index :: (Word, Word) -> Word -> Int #

unsafeIndex :: (Word, Word) -> Word -> Int

inRange :: (Word, Word) -> Word -> Bool #

rangeSize :: (Word, Word) -> Int #

unsafeRangeSize :: (Word, Word) -> Int

Storable Word 

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Bits Word 
FiniteBits Word 
IArray UArray Word 

Methods

bounds :: Ix i => UArray i Word -> (i, i) #

numElements :: Ix i => UArray i Word -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word)] -> UArray i Word

unsafeAt :: Ix i => UArray i Word -> Int -> Word

unsafeReplace :: Ix i => UArray i Word -> [(Int, Word)] -> UArray i Word

unsafeAccum :: Ix i => (Word -> e' -> Word) -> UArray i Word -> [(Int, e')] -> UArray i Word

unsafeAccumArray :: Ix i => (Word -> e' -> Word) -> Word -> (i, i) -> [(Int, e')] -> UArray i Word

Functor (URec Word) 

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Foldable (URec Word) 

Methods

fold :: Monoid m => URec Word m -> m #

foldMap :: Monoid m => (a -> m) -> URec Word a -> m #

foldr :: (a -> b -> b) -> b -> URec Word a -> b #

foldr' :: (a -> b -> b) -> b -> URec Word a -> b #

foldl :: (b -> a -> b) -> b -> URec Word a -> b #

foldl' :: (b -> a -> b) -> b -> URec Word a -> b #

foldr1 :: (a -> a -> a) -> URec Word a -> a #

foldl1 :: (a -> a -> a) -> URec Word a -> a #

toList :: URec Word a -> [a] #

null :: URec Word a -> Bool #

length :: URec Word a -> Int #

elem :: Eq a => a -> URec Word a -> Bool #

maximum :: Ord a => URec Word a -> a #

minimum :: Ord a => URec Word a -> a #

sum :: Num a => URec Word a -> a #

product :: Num a => URec Word a -> a #

Traversable (URec Word) 

Methods

traverse :: Applicative f => (a -> f b) -> URec Word a -> f (URec Word b) #

sequenceA :: Applicative f => URec Word (f a) -> f (URec Word a) #

mapM :: Monad m => (a -> m b) -> URec Word a -> m (URec Word b) #

sequence :: Monad m => URec Word (m a) -> m (URec Word a) #

Generic1 (URec Word) 

Associated Types

type Rep1 (URec Word :: * -> *) :: * -> * #

Methods

from1 :: URec Word a -> Rep1 (URec Word) a #

to1 :: Rep1 (URec Word) a -> URec Word a #

MArray (STUArray s) Word (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word -> ST s Int

newArray :: Ix i => (i, i) -> Word -> ST s (STUArray s i Word) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word)

unsafeRead :: Ix i => STUArray s i Word -> Int -> ST s Word

unsafeWrite :: Ix i => STUArray s i Word -> Int -> Word -> ST s ()

Eq (URec Word p) 

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p) 

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Show (URec Word p) 

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Generic (URec Word p) 

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

data URec Word

Used for marking occurrences of Word#

data URec Word = UWord {}
type Rep1 (URec Word) 
type Rep1 (URec Word) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))
type Rep (URec Word p) 
type Rep (URec Word p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord))

8 bit Word

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8 
Num Word8 
Ord Word8 

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8 
Real Word8 

Methods

toRational :: Word8 -> Rational #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8 
Storable Word8 

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Bits Word8 
FiniteBits Word8 
IArray UArray Word8 

Methods

bounds :: Ix i => UArray i Word8 -> (i, i) #

numElements :: Ix i => UArray i Word8 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word8)] -> UArray i Word8

unsafeAt :: Ix i => UArray i Word8 -> Int -> Word8

unsafeReplace :: Ix i => UArray i Word8 -> [(Int, Word8)] -> UArray i Word8

unsafeAccum :: Ix i => (Word8 -> e' -> Word8) -> UArray i Word8 -> [(Int, e')] -> UArray i Word8

unsafeAccumArray :: Ix i => (Word8 -> e' -> Word8) -> Word8 -> (i, i) -> [(Int, e')] -> UArray i Word8

MArray (STUArray s) Word8 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word8 -> ST s Int

newArray :: Ix i => (i, i) -> Word8 -> ST s (STUArray s i Word8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8)

unsafeRead :: Ix i => STUArray s i Word8 -> Int -> ST s Word8

unsafeWrite :: Ix i => STUArray s i Word8 -> Int -> Word8 -> ST s ()

64 bit Integer

data Int64 :: * #

64-bit signed integer type

Instances

Bounded Int64 
Enum Int64 
Eq Int64 

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Integral Int64 
Num Int64 
Ord Int64 

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

(>=) :: Int64 -> Int64 -> Bool #

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64 
Real Int64 

Methods

toRational :: Int64 -> Rational #

Show Int64 

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64 
Storable Int64 

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64 
FiniteBits Int64 
IArray UArray Int64 

Methods

bounds :: Ix i => UArray i Int64 -> (i, i) #

numElements :: Ix i => UArray i Int64 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Int64)] -> UArray i Int64

unsafeAt :: Ix i => UArray i Int64 -> Int -> Int64

unsafeReplace :: Ix i => UArray i Int64 -> [(Int, Int64)] -> UArray i Int64

unsafeAccum :: Ix i => (Int64 -> e' -> Int64) -> UArray i Int64 -> [(Int, e')] -> UArray i Int64

unsafeAccumArray :: Ix i => (Int64 -> e' -> Int64) -> Int64 -> (i, i) -> [(Int, e')] -> UArray i Int64

MArray (STUArray s) Int64 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Int64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int64 -> ST s Int

newArray :: Ix i => (i, i) -> Int64 -> ST s (STUArray s i Int64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64)

unsafeRead :: Ix i => STUArray s i Int64 -> Int -> ST s Int64

unsafeWrite :: Ix i => STUArray s i Int64 -> Int -> Int64 -> ST s ()

CDouble

newtype CDouble :: * #

Haskell type representing the C double type.

Constructors

CDouble Double 

Instances

Enum CDouble 
Eq CDouble 

Methods

(==) :: CDouble -> CDouble -> Bool #

(/=) :: CDouble -> CDouble -> Bool #

Floating CDouble 
Fractional CDouble 
Num CDouble 
Ord CDouble 
Read CDouble 
Real CDouble 
RealFloat CDouble 
RealFrac CDouble 

Methods

properFraction :: Integral b => CDouble -> (b, CDouble) #

truncate :: Integral b => CDouble -> b #

round :: Integral b => CDouble -> b #

ceiling :: Integral b => CDouble -> b #

floor :: Integral b => CDouble -> b #

Show CDouble 
Storable CDouble 

CChar

data CChar :: * #

Haskell type representing the C char type.

Instances

Bounded CChar 
Enum CChar 
Eq CChar 

Methods

(==) :: CChar -> CChar -> Bool #

(/=) :: CChar -> CChar -> Bool #

Integral CChar 
Num CChar 
Ord CChar 

Methods

compare :: CChar -> CChar -> Ordering #

(<) :: CChar -> CChar -> Bool #

(<=) :: CChar -> CChar -> Bool #

(>) :: CChar -> CChar -> Bool #

(>=) :: CChar -> CChar -> Bool #

max :: CChar -> CChar -> CChar #

min :: CChar -> CChar -> CChar #

Read CChar 
Real CChar 

Methods

toRational :: CChar -> Rational #

Show CChar 

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Storable CChar 

Methods

sizeOf :: CChar -> Int #

alignment :: CChar -> Int #

peekElemOff :: Ptr CChar -> Int -> IO CChar #

pokeElemOff :: Ptr CChar -> Int -> CChar -> IO () #

peekByteOff :: Ptr b -> Int -> IO CChar #

pokeByteOff :: Ptr b -> Int -> CChar -> IO () #

peek :: Ptr CChar -> IO CChar #

poke :: Ptr CChar -> CChar -> IO () #

Bits CChar 
FiniteBits CChar 

newtype CWchar :: * #

Haskell type representing the C wchar_t type.

Constructors

CWchar Int32 

Instances

Bounded CWchar 
Enum CWchar 
Eq CWchar 

Methods

(==) :: CWchar -> CWchar -> Bool #

(/=) :: CWchar -> CWchar -> Bool #

Integral CWchar 
Num CWchar 
Ord CWchar 
Read CWchar 
Real CWchar 
Show CWchar 
Storable CWchar 
Bits CWchar 
FiniteBits CWchar 

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) 

Methods

bounds :: Ix i => UArray i (Ptr a) -> (i, i) #

numElements :: Ix i => UArray i (Ptr a) -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Ptr a)] -> UArray i (Ptr a)

unsafeAt :: Ix i => UArray i (Ptr a) -> Int -> Ptr a

unsafeReplace :: Ix i => UArray i (Ptr a) -> [(Int, Ptr a)] -> UArray i (Ptr a)

unsafeAccum :: Ix i => (Ptr a -> e' -> Ptr a) -> UArray i (Ptr a) -> [(Int, e')] -> UArray i (Ptr a)

unsafeAccumArray :: Ix i => (Ptr a -> e' -> Ptr a) -> Ptr a -> (i, i) -> [(Int, e')] -> UArray i (Ptr a)

Eq (Ptr a) 

Methods

(==) :: Ptr a -> Ptr a -> Bool #

(/=) :: Ptr a -> Ptr a -> Bool #

Functor (URec (Ptr ())) 

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a #

Ord (Ptr a) 

Methods

compare :: Ptr a -> Ptr a -> Ordering #

(<) :: Ptr a -> Ptr a -> Bool #

(<=) :: Ptr a -> Ptr a -> Bool #

(>) :: Ptr a -> Ptr a -> Bool #

(>=) :: Ptr a -> Ptr a -> Bool #

max :: Ptr a -> Ptr a -> Ptr a #

min :: Ptr a -> Ptr a -> Ptr a #

Show (Ptr a) 

Methods

showsPrec :: Int -> Ptr a -> ShowS #

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Foldable (URec (Ptr ())) 

Methods

fold :: Monoid m => URec (Ptr ()) m -> m #

foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m #

foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b #

foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b #

foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b #

foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b #

foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a #

foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a #

toList :: URec (Ptr ()) a -> [a] #

null :: URec (Ptr ()) a -> Bool #

length :: URec (Ptr ()) a -> Int #

elem :: Eq a => a -> URec (Ptr ()) a -> Bool #

maximum :: Ord a => URec (Ptr ()) a -> a #

minimum :: Ord a => URec (Ptr ()) a -> a #

sum :: Num a => URec (Ptr ()) a -> a #

product :: Num a => URec (Ptr ()) a -> a #

Traversable (URec (Ptr ())) 

Methods

traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) #

sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) #

mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) #

sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) #

Generic1 (URec (Ptr ())) 

Associated Types

type Rep1 (URec (Ptr ()) :: * -> *) :: * -> * #

Methods

from1 :: URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a #

to1 :: Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a #

Storable (Ptr a) 

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () #

peek :: Ptr (Ptr a) -> IO (Ptr a) #

poke :: Ptr (Ptr a) -> Ptr a -> IO () #

MArray (STUArray s) (Ptr a) (ST s) 

Methods

getBounds :: Ix i => STUArray s i (Ptr a) -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i (Ptr a) -> ST s Int

newArray :: Ix i => (i, i) -> Ptr a -> ST s (STUArray s i (Ptr a)) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i (Ptr a)) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i (Ptr a))

unsafeRead :: Ix i => STUArray s i (Ptr a) -> Int -> ST s (Ptr a)

unsafeWrite :: Ix i => STUArray s i (Ptr a) -> Int -> Ptr a -> ST s ()

Eq (URec (Ptr ()) p) 

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

Ord (URec (Ptr ()) p) 

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

Generic (URec (Ptr ()) p) 

Associated Types

type Rep (URec (Ptr ()) p) :: * -> * #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

type Rep1 (URec (Ptr ())) 
type Rep1 (URec (Ptr ())) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UAddr" PrefixI True) (S1 (MetaSel (Just Symbol "uAddr#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UAddr))
data URec (Ptr ())

Used for marking occurrences of Addr#

data URec (Ptr ()) = UAddr {}
type Rep (URec (Ptr ()) p) 
type Rep (URec (Ptr ()) p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UAddr" PrefixI True) (S1 (MetaSel (Just Symbol "uAddr#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UAddr))

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.

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) 

Methods

bounds :: Ix i => UArray i (FunPtr a) -> (i, i) #

numElements :: Ix i => UArray i (FunPtr a) -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, FunPtr a)] -> UArray i (FunPtr a)

unsafeAt :: Ix i => UArray i (FunPtr a) -> Int -> FunPtr a

unsafeReplace :: Ix i => UArray i (FunPtr a) -> [(Int, FunPtr a)] -> UArray i (FunPtr a)

unsafeAccum :: Ix i => (FunPtr a -> e' -> FunPtr a) -> UArray i (FunPtr a) -> [(Int, e')] -> UArray i (FunPtr a)

unsafeAccumArray :: Ix i => (FunPtr a -> e' -> FunPtr a) -> FunPtr a -> (i, i) -> [(Int, e')] -> UArray i (FunPtr a)

Eq (FunPtr a) 

Methods

(==) :: FunPtr a -> FunPtr a -> Bool #

(/=) :: FunPtr a -> FunPtr a -> Bool #

Ord (FunPtr a) 

Methods

compare :: FunPtr a -> FunPtr a -> Ordering #

(<) :: FunPtr a -> FunPtr a -> Bool #

(<=) :: FunPtr a -> FunPtr a -> Bool #

(>) :: FunPtr a -> FunPtr a -> Bool #

(>=) :: FunPtr a -> FunPtr a -> Bool #

max :: FunPtr a -> FunPtr a -> FunPtr a #

min :: FunPtr a -> FunPtr a -> FunPtr a #

Show (FunPtr a) 

Methods

showsPrec :: Int -> FunPtr a -> ShowS #

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Storable (FunPtr a) 

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () #

MArray (STUArray s) (FunPtr a) (ST s) 

Methods

getBounds :: Ix i => STUArray s i (FunPtr a) -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i (FunPtr a) -> ST s Int

newArray :: Ix i => (i, i) -> FunPtr a -> ST s (STUArray s i (FunPtr a)) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i (FunPtr a)) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i (FunPtr a))

unsafeRead :: Ix i => STUArray s i (FunPtr a) -> Int -> ST s (FunPtr a)

unsafeWrite :: Ix i => STUArray s i (FunPtr a) -> Int -> FunPtr a -> ST s ()