Copyright | (c) The FFI Task Force 2000-2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | ffi@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Synopsis
- data Ptr a = Ptr Addr#
- data FunPtr a = FunPtr 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
- nullFunPtr :: FunPtr a
- castFunPtr :: FunPtr a -> FunPtr b
- castFunPtrToPtr :: FunPtr a -> Ptr b
- castPtrToFunPtr :: Ptr a -> FunPtr b
Documentation
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 type Ptr
aa
.
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
Generic1 (URec (Ptr ()) :: k -> Type) Source # | |
Data a => Data (Ptr a) Source # | Since: base-4.8.0.0 |
Defined in Data.Data 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 :: forall r r'. (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 # | |
Foldable (UAddr :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UAddr m -> m Source # foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source # foldr :: (a -> b -> b) -> b -> UAddr a -> b Source # foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source # foldl :: (b -> a -> b) -> b -> UAddr a -> b Source # foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source # foldr1 :: (a -> a -> a) -> UAddr a -> a Source # foldl1 :: (a -> a -> a) -> UAddr a -> a Source # toList :: UAddr a -> [a] Source # null :: UAddr a -> Bool Source # length :: UAddr a -> Int Source # elem :: Eq a => a -> UAddr a -> Bool Source # maximum :: Ord a => UAddr a -> a Source # minimum :: Ord a => UAddr a -> a Source # | |
Traversable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 |
Storable (Ptr a) Source # | Since: base-2.1 |
Defined in Foreign.Storable 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 # | |
Show (Ptr a) Source # | Since: base-2.1 |
Eq (Ptr a) Source # | Since: base-2.1 |
Ord (Ptr a) Source # | Since: base-2.1 |
Functor (URec (Ptr ()) :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Generic (URec (Ptr ()) p) Source # | |
Eq (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 |
Ord (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # | |
data URec (Ptr ()) (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec (Ptr ()) :: k -> Type) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
A value of type
is a pointer to a function callable
from foreign code. The type FunPtr
aa
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
,Double
,Float
,Bool
,Int8
,Int16
,Int32
,Int64
,Word8
,Word16
,Word32
,Word64
,
,Ptr
a
,FunPtr
a
or a renaming of any of these usingStablePtr
anewtype
. - the return type is either a marshallable foreign type or has the form
whereIO
tt
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 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
Storable (FunPtr a) Source # | Since: base-2.1 |
Defined in Foreign.Storable 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 # | |
Show (FunPtr a) Source # | Since: base-2.1 |
Eq (FunPtr a) Source # | |
Ord (FunPtr a) Source # | |
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)
nullFunPtr :: FunPtr a Source #
The constant nullFunPtr
contains a
distinguished value of FunPtr
that is not
associated with a valid memory location.
Unsafe functions
castFunPtrToPtr :: FunPtr a -> Ptr b Source #