|  | 
| | Foreign.Ptr | | Portability | portable |  | Stability | provisional |  | Maintainer | ffi@haskell.org | 
 | 
 | 
|  | 
|  | 
|  | 
| 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 | 
|  | 
|  | 
| | 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 |  |  | 
 | 
|  | 
|  | 
| The constant nullPtr contains a distinguished value of Ptr
 that is not associated with a valid memory location. | 
|  | 
|  | 
| The castPtr function casts a pointer from one type to another. | 
|  | 
|  | 
| Advances the given address by the given offset in bytes. | 
|  | 
|  | 
| 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. | 
|  | 
|  | 
| Computes the offset required to get from the second to the first
 argument.  We have 
  p2 == p1 `plusPtr` (p2 `minusPtr` p1)
 | 
|  | 
| Function pointers | 
|  | 
|  | 
| | 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 |  |  | 
 | 
|  | 
|  | 
| The constant nullFunPtr contains a
 distinguished value of FunPtr that is not
 associated with a valid memory location. | 
|  | 
|  | 
| Casts a FunPtr to a FunPtr of a different type. | 
|  | 
|  | 
| 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.
 | 
|  | 
|  | 
| 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.
 | 
|  | 
|  | 
| 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 | 
|  | 
|  | 
| | A signed integral type that can be losslessly converted to and from
 Ptr. |  |  Instances |  |  | 
 | 
|  | 
|  | 
| casts a Ptr to an IntPtr | 
|  | 
|  | 
| casts an IntPtr to a Ptr | 
|  | 
|  | 
| | An unsigned integral type that can be losslessly converted to and from
 Ptr. |  |  Instances |  |  | 
 | 
|  | 
|  | 
| casts a Ptr to a WordPtr | 
|  | 
|  | 
| casts a WordPtr to a Ptr | 
|  | 
| Produced by Haddock version 2.6.1 |