Copyright | (c) Dong Han 2020 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provide a lightweight foreign pointer, support c initializer and finalizer only.
Synopsis
- data CPtr a
- newCPtr' :: IO (Ptr a) -> FunPtr (Ptr a -> IO b) -> IO (CPtr a)
- newCPtrUnsafe :: (MutableByteArray# RealWorld -> IO r) -> FunPtr (Ptr a -> IO b) -> IO (CPtr a, r)
- newCPtr :: (Ptr (Ptr a) -> IO r) -> FunPtr (Ptr a -> IO b) -> IO (CPtr a, r)
- withCPtr :: CPtr a -> (Ptr a -> IO b) -> IO b
- withCPtrsUnsafe :: forall a b. [CPtr a] -> (BA# (Ptr a) -> Int -> IO b) -> IO b
- withCPtrs :: forall a b. [CPtr a] -> (Ptr (Ptr a) -> Int -> IO b) -> IO b
- data Ptr a
- nullPtr :: Ptr a
- data FunPtr a
CPtr type
Lightweight foreign pointers.
Initialize a CPtr
with initializer which return an allocated pointer.
:: (MutableByteArray# RealWorld -> IO r) | initializer |
-> FunPtr (Ptr a -> IO b) | finalizer |
-> IO (CPtr a, r) |
Initialize a CPtr
with initializer(must be unsafe FFI) and finalizer.
The initializer will receive a pointer of pointer so that it can do allocation and write pointer back.
Initialize a CPtr
with initializer and finalizer.
The initializer will receive a pointer of pointer so that it can do allocation and write pointer back.
withCPtrsUnsafe :: forall a b. [CPtr a] -> (BA# (Ptr a) -> Int -> IO b) -> IO b Source #
Pass a list of 'CPtr Foo' as foo**
. USE THIS FUNCTION WITH UNSAFE FFI ONLY!
withCPtrs :: forall a b. [CPtr a] -> (Ptr (Ptr a) -> Int -> IO b) -> IO b Source #
Pass a list of 'CPtr Foo' as foo**
.
Ptr type
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
NFData1 Ptr | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Generic1 (URec (Ptr ()) :: k -> Type) | Since: base-4.9.0.0 |
Eq (Ptr a) | Since: base-2.1 |
Data a => Data (Ptr a) | 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) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) # dataTypeOf :: Ptr a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) # gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) # | |
Ord (Ptr a) | Since: base-2.1 |
Show (Ptr a) | Since: base-2.1 |
Foldable (UAddr :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UAddr m -> m # foldMap :: Monoid m => (a -> m) -> UAddr a -> m # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m # foldr :: (a -> b -> b) -> b -> UAddr a -> b # foldr' :: (a -> b -> b) -> b -> UAddr a -> b # foldl :: (b -> a -> b) -> b -> UAddr a -> b # foldl' :: (b -> a -> b) -> b -> UAddr a -> b # foldr1 :: (a -> a -> a) -> UAddr a -> a # foldl1 :: (a -> a -> a) -> UAddr a -> a # elem :: Eq a => a -> UAddr a -> Bool # maximum :: Ord a => UAddr a -> a # minimum :: Ord a => UAddr a -> a # | |
Traversable (UAddr :: Type -> Type) | Since: base-4.9.0.0 |
NFData (Ptr a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
Hashable (Ptr a) | |
Defined in Data.Hashable.Class | |
Prim (Ptr a) | |
Defined in Data.Primitive.Types alignment# :: Ptr a -> Int# # indexByteArray# :: ByteArray# -> Int# -> Ptr a # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Ptr a #) # writeByteArray# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Ptr a -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Ptr a # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Ptr a #) # writeOffAddr# :: Addr# -> Int# -> Ptr a -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Ptr a -> State# s -> State# s # | |
Unaligned (Ptr a) Source # | |
Defined in Z.Data.Array.Unaligned unalignedSize :: UnalignedSize (Ptr a) Source # indexWord8ArrayAs# :: ByteArray# -> Int# -> Ptr a Source # readWord8ArrayAs# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Ptr a #) Source # writeWord8ArrayAs# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s Source # peekMBA :: MutableByteArray# RealWorld -> Int -> IO (Ptr a) Source # pokeMBA :: MutableByteArray# RealWorld -> Int -> Ptr a -> IO () Source # | |
Print (Ptr a) Source # | |
Defined in Z.Data.Text.Print | |
Functor (URec (Ptr ()) :: Type -> Type) | Since: base-4.9.0.0 |
Eq (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Ord (URec (Ptr ()) p) | Since: base-4.9.0.0 |
Defined in GHC.Generics 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 # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # | |
Generic (URec (Ptr ()) p) | Since: base-4.9.0.0 |
data URec (Ptr ()) (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec (Ptr ()) :: k -> Type) | |
Defined in GHC.Generics | |
type Rep (URec (Ptr ()) p) | |
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
NFData1 FunPtr | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq (FunPtr a) | |
Ord (FunPtr a) | |
Show (FunPtr a) | Since: base-2.1 |
NFData (FunPtr a) | Since: deepseq-1.4.2.0 |
Defined in Control.DeepSeq | |
Hashable (FunPtr a) | |
Defined in Data.Hashable.Class | |
Prim (FunPtr a) | |
Defined in Data.Primitive.Types alignment# :: FunPtr a -> Int# # indexByteArray# :: ByteArray# -> Int# -> FunPtr a # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, FunPtr a #) # writeByteArray# :: MutableByteArray# s -> Int# -> FunPtr a -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> FunPtr a -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> FunPtr a # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, FunPtr a #) # writeOffAddr# :: Addr# -> Int# -> FunPtr a -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> FunPtr a -> State# s -> State# s # |