Haskell Hierarchical Libraries (base package)ContentsIndex
GHC.Ptr
Portability non-portable (GHC Extensions)
Stability internal
Maintainer ffi@haskell.org
Description
The Ptr and FunPtr types and operations.
Synopsis
data Ptr a = Ptr Addr#
nullPtr :: Ptr a
castPtr :: Ptr a -> Ptr b
plusPtr :: Ptr a -> Int -> Ptr b
alignPtr :: Ptr a -> Int -> Ptr a
minusPtr :: Ptr a -> Ptr b -> Int
data FunPtr a = FunPtr Addr#
nullFunPtr :: FunPtr a
castFunPtr :: FunPtr a -> FunPtr b
castFunPtrToPtr :: FunPtr a -> Ptr b
castPtrToFunPtr :: Ptr a -> FunPtr b
Documentation
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.

Constructors
Ptr Addr#
Instances
IArray UArray (Ptr a)
Ix ix => Eq (UArray ix (Ptr a))
Ix ix => Ord (UArray ix (Ptr a))
MArray (STUArray s) (Ptr a) (ST s)
IArray (IOToDiffArray IOUArray) (Ptr a)
MArray IOUArray (Ptr a) IO
Typeable a => Typeable (Ptr a)
Show (Ptr a)
Storable (Ptr a)
Eq (Ptr a)
Ord (Ptr a)
nullPtr :: Ptr a
The constant nullPtr contains a distinguished value of Ptr that is not associated with a valid memory location.
castPtr :: Ptr a -> Ptr b
The castPtr function casts a pointer from one type to another.
plusPtr :: Ptr a -> Int -> Ptr b
Advances the given address by the given offset in bytes.
alignPtr :: Ptr a -> Int -> Ptr a
Given an arbitrary address and an alignment constraint, alignPtr yields the next higher address that fulfills the alignment constraint. An alignment constraint x is fulfilled by any address divisible by x. This operation is idempotent.
minusPtr :: Ptr a -> Ptr b -> Int

Computes the offset required to get from the first to the second argument. We have

 p2 == p1 `plusPtr` (p2 `minusPtr` p1)
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
Constructors
FunPtr Addr#
Instances
IArray UArray (FunPtr a)
Ix ix => Eq (UArray ix (FunPtr a))
Ix ix => Ord (UArray ix (FunPtr a))
MArray (STUArray s) (FunPtr a) (ST s)
IArray (IOToDiffArray IOUArray) (FunPtr a)
MArray IOUArray (FunPtr a) IO
Show (FunPtr a)
Storable (FunPtr a)
Eq (FunPtr a)
Ord (FunPtr a)
nullFunPtr :: FunPtr a
The constant nullFunPtr contains a distinguished value of FunPtr that is not associated with a valid memory location.
castFunPtr :: FunPtr a -> FunPtr b
Casts a FunPtr to a FunPtr of a different type.
castFunPtrToPtr :: FunPtr a -> Ptr b

Casts a FunPtr to a Ptr.

Note: this is valid only on architectures where data and function pointers range over the same set of addresses, and should only be used for bindings to external libraries whose interface already relies on this assumption.

castPtrToFunPtr :: Ptr a -> FunPtr b

Casts a Ptr to a FunPtr.

Note: this is valid only on architectures where data and function pointers range over the same set of addresses, and should only be used for bindings to external libraries whose interface already relies on this assumption.

Produced by Haddock version 0.6