| Copyright | (c) The FFI task force 2001 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Maintainer | ffi@haskell.org |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Foreign.Ptr
Description
This module provides typed pointers to foreign data. It is part of the Foreign Function Interface (FFI) and will normally be imported via theForeign module.
A value of type represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of typePtr aa.
The typea will often be an instance of classStorable 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 Cstruct.
| Generic1 (URec (Ptr ()) :: k ->Type)Source# | |
| Eq (Ptr a)Source# | Since: 2.1 |
| Data a =>Data (Ptr a)Source# | Since: 4.8.0.0 |
Instance detailsDefined inData.Data 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 ->ConstrSource# dataTypeOf ::Ptr a ->DataTypeSource# 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 aSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Ptr a -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Ptr a -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Ptr a -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Ptr a -> uSource# 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# | Since: 2.1 |
| Show (Ptr a)Source# | Since: 2.1 |
| Storable (Ptr a)Source# | Since: 2.1 |
Instance detailsDefined inForeign.Storable | |
| Functor (URec (Ptr ()) ::Type ->Type)Source# | Since: 4.9.0.0 |
| Foldable (URec (Ptr ()) ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>URec (Ptr ()) m -> mSource# foldMap ::Monoid m => (a -> m) ->URec (Ptr ()) a -> mSource# foldr :: (a -> b -> b) -> b ->URec (Ptr ()) a -> bSource# foldr' :: (a -> b -> b) -> b ->URec (Ptr ()) a -> bSource# foldl :: (b -> a -> b) -> b ->URec (Ptr ()) a -> bSource# foldl' :: (b -> a -> b) -> b ->URec (Ptr ()) a -> bSource# foldr1 :: (a -> a -> a) ->URec (Ptr ()) a -> aSource# foldl1 :: (a -> a -> a) ->URec (Ptr ()) a -> aSource# toList ::URec (Ptr ()) a -> [a]Source# null ::URec (Ptr ()) a ->BoolSource# length ::URec (Ptr ()) a ->IntSource# elem ::Eq a => a ->URec (Ptr ()) a ->BoolSource# maximum ::Ord a =>URec (Ptr ()) a -> aSource# minimum ::Ord a =>URec (Ptr ()) a -> aSource# | |
| Traversable (URec (Ptr ()) ::Type ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Traversable Methods traverse ::Applicative f => (a -> f b) ->URec (Ptr ()) a -> f (URec (Ptr ()) b)Source# sequenceA ::Applicative f =>URec (Ptr ()) (f a) -> f (URec (Ptr ()) a)Source# mapM ::Monad m => (a -> m b) ->URec (Ptr ()) a -> m (URec (Ptr ()) b)Source# sequence ::Monad m =>URec (Ptr ()) (m a) -> m (URec (Ptr ()) a)Source# | |
| Eq (URec (Ptr ()) p)Source# | Since: 4.9.0.0 |
| Ord (URec (Ptr ()) p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics 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# | |
| Generic (URec (Ptr ()) p)Source# | |
| dataURec (Ptr ()) (p :: k)Source# | Used for marking occurrences of Since: 4.9.0.0 |
| typeRep1 (URec (Ptr ()) :: k ->Type)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
| typeRep (URec (Ptr ()) p)Source# | Since: 4.9.0.0 |
Instance detailsDefined inGHC.Generics | |
alignPtr ::Ptr a ->Int ->Ptr aSource#
Given an arbitrary address and an alignment constraint,alignPtr yields the next higher address that fulfills the alignment constraint. An alignment constraintx is fulfilled by any address divisible byx. This operation is idempotent.
minusPtr ::Ptr a ->Ptr b ->IntSource#
Computes the offset required to get from the second to the first argument. We have
p2 == p1 `plusPtr` (p2 `minusPtr` p1)
A value of type is a pointer to a function callable from foreign code. The typeFunPtr aa will normally be aforeign type, a function type with zero or more arguments where
Char,Int,Double,Float,Bool,Int8,Int16,Int32,Int64,Word8,Word16,Word32,Word64,Ptr a,FunPtr a,StablePtr a or a renaming of any of these usingnewtype.IO t wheret is a marshallable foreign type or().A value of type may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import likeFunPtr a
foreign import ccall "stdlib.h &free" p_free :: FunPtr (Ptr a -> IO ())
or a pointer to a Haskell function created using awrapper stub declared to produce aFunPtr of the correct type. For example:
type Compare = Int -> Int -> Boolforeign import ccall "wrapper" mkCompare :: Compare -> IO (FunPtr Compare)
Calls to wrapper stubs likemkCompare allocate storage, which should be released withfreeHaskellFunPtr when no longer required.
To convertFunPtr values to corresponding Haskell functions, one can define adynamic stub for the specific foreign type, e.g.
type IntFunction = CInt -> IO ()foreign import ccall "dynamic" mkFun :: FunPtr IntFunction -> IntFunction
| Eq (FunPtr a)Source# | |
| Ord (FunPtr a)Source# | |
| Show (FunPtr a)Source# | Since: 2.1 |
| Storable (FunPtr a)Source# | Since: 2.1 |
Instance detailsDefined inForeign.Storable Methods sizeOf ::FunPtr a ->IntSource# alignment ::FunPtr a ->IntSource# 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# | |
The constantnullFunPtr contains a distinguished value ofFunPtr that is not associated with a valid memory location.
castFunPtrToPtr ::FunPtr a ->Ptr bSource#
castPtrToFunPtr ::Ptr a ->FunPtr bSource#
freeHaskellFunPtr ::FunPtr a ->IO ()Source#
Release the storage associated with the givenFunPtr, 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.
A signed integral type that can be losslessly converted to and fromPtr. This type is also compatible with the C99 typeintptr_t, and can be marshalled to and from that type safely.
ptrToIntPtr ::Ptr a ->IntPtrSource#
casts aPtr to anIntPtr
intPtrToPtr ::IntPtr ->Ptr aSource#
casts anIntPtr to aPtr
An unsigned integral type that can be losslessly converted to and fromPtr. This type is also compatible with the C99 typeuintptr_t, and can be marshalled to and from that type safely.
ptrToWordPtr ::Ptr a ->WordPtrSource#
casts aPtr to aWordPtr
wordPtrToPtr ::WordPtr ->Ptr aSource#
casts aWordPtr to aPtr
Produced byHaddock version 2.20.0