base-4.8.1.0: Basic libraries

Copyright(c) The FFI task force 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerffi@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Foreign.Ptr

Contents

Description

This module provides typed pointers to foreign data. It is part of the Foreign Function Interface (FFI) and will normally be imported via the Foreign module.

Synopsis

Data pointers

data Ptr a Source

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

Eq (Ptr a) Source 

Methods

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

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

(Data a, Typeable * a) => Data (Ptr a) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) Source

toConstr :: Ptr a -> Constr Source

dataTypeOf :: Ptr a -> DataType Source

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) Source

gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source

Ord (Ptr a) Source 

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

Methods

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

show :: Ptr a -> String Source

showList :: [Ptr a] -> ShowS Source

Storable (Ptr a) Source 

Methods

sizeOf :: Ptr a -> Int Source

alignment :: Ptr a -> Int Source

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

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

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

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

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

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

nullPtr :: Ptr a Source

The constant nullPtr contains a distinguished value of Ptr that is not associated with a valid memory location.

castPtr :: Ptr a -> Ptr b Source

The castPtr function casts a pointer from one type to another.

plusPtr :: Ptr a -> Int -> Ptr b Source

Advances the given address by the given offset in bytes.

alignPtr :: Ptr a -> Int -> Ptr a Source

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 Source

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

p2 == p1 `plusPtr` (p2 `minusPtr` p1)

Function pointers

data FunPtr a Source

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

Eq (FunPtr a) Source 

Methods

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

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

Ord (FunPtr a) Source 

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) Source 
Storable (FunPtr a) Source 

Methods

sizeOf :: FunPtr a -> Int Source

alignment :: FunPtr a -> Int Source

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

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

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

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

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

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

nullFunPtr :: FunPtr a Source

The constant nullFunPtr contains a distinguished value of FunPtr that is not associated with a valid memory location.

castFunPtr :: FunPtr a -> FunPtr b Source

Casts a FunPtr to a FunPtr of a different type.

castFunPtrToPtr :: FunPtr a -> Ptr b Source

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 Source

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.

freeHaskellFunPtr :: FunPtr a -> IO () Source

Release the storage associated with the given FunPtr, which must have been obtained from a wrapper stub. This should be called whenever the return value from a foreign import wrapper function is no longer required; otherwise, the storage it uses will leak.

Integral types with lossless conversion to and from pointers

data IntPtr Source

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 Source 
Enum IntPtr Source 
Eq IntPtr Source 

Methods

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

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

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

ptrToIntPtr :: Ptr a -> IntPtr Source

casts a Ptr to an IntPtr

intPtrToPtr :: IntPtr -> Ptr a Source

casts an IntPtr to a Ptr

data WordPtr Source

An unsigned integral type that can be losslessly converted to and from Ptr. This type is also compatible with the C99 type uintptr_t, and can be marshalled to and from that type safely.

Instances

Bounded WordPtr Source 
Enum WordPtr Source 
Eq WordPtr Source 

Methods

(==) :: WordPtr -> WordPtr -> Bool

(/=) :: WordPtr -> WordPtr -> Bool

Integral WordPtr Source 
Num WordPtr Source 
Ord WordPtr Source 
Read WordPtr Source 
Real WordPtr Source 
Show WordPtr Source 
FiniteBits WordPtr Source 
Bits WordPtr Source 
Storable WordPtr Source 

ptrToWordPtr :: Ptr a -> WordPtr Source

casts a Ptr to a WordPtr

wordPtrToPtr :: WordPtr -> Ptr a Source

casts a WordPtr to a Ptr