| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
HsForeign.Primitive
Contents
Synopsis
- newtype BA# a = BA# ByteArray#
- newtype MBA# a = MBA# (MutableByteArray# RealWorld)
- newtype BAArray# a = BAArray# ArrayArray#
- withPrim :: forall a b. Prim a => a -> (Ptr a -> IO b) -> IO (a, b)
- allocPrim :: forall a b. Prim a => (Ptr a -> IO b) -> IO (a, b)
- withPrimUnsafe :: Prim a => a -> (MBA# a -> IO b) -> IO (a, b)
- allocPrimUnsafe :: Prim a => (MBA# a -> IO b) -> IO (a, b)
- withPrimArray :: Prim a => PrimArray a -> (Ptr a -> Int -> IO b) -> IO b
- withPrimList :: Prim a => [a] -> (Ptr a -> Int -> IO b) -> IO b
- allocPrimArray :: forall a b. Prim a => Int -> (Ptr a -> IO b) -> IO (PrimArray a, b)
- withPrimArrayUnsafe :: Prim a => PrimArray a -> (BA# a -> Int -> IO b) -> IO b
- allocPrimArrayUnsafe :: forall a b. Prim a => Int -> (MBA# a -> IO b) -> IO (PrimArray a, b)
- withPrimArrayList :: Prim a => [PrimArray a] -> (Ptr (Ptr a) -> Int -> IO b) -> IO b
- withPrimArrayListUnsafe :: [PrimArray a] -> (BAArray# a -> Int -> IO b) -> IO b
- withForeignPtrList :: [ForeignPtr a] -> (Ptr (Ptr a) -> Int -> IO b) -> IO b
- withMutablePrimArrayContents :: MutablePrimArray RealWorld a -> (Ptr a -> IO b) -> IO b
- withPrimArrayContents :: PrimArray a -> (Ptr a -> IO b) -> IO b
- byteArrayContents# :: ByteArray# -> Addr#
- mutableByteArrayContents# :: MutableByteArray# s -> Addr#
- module Data.Primitive
- module Control.Monad.Primitive
Documentation
Constructors
| BA# ByteArray# |
Constructors
| BAArray# ArrayArray# |
withPrim :: forall a b. Prim a => a -> (Ptr a -> IO b) -> IO (a, b) Source #
Create an one element primitive array and use it as a pointer to the primitive element.
Don't pass a forever loop to this function, see #14346.
allocPrim :: forall a b. Prim a => (Ptr a -> IO b) -> IO (a, b) Source #
like withPrim, but don't write initial value.
withPrimUnsafe :: Prim a => a -> (MBA# a -> IO b) -> IO (a, b) Source #
Create an one element primitive array and use it as a pointer to the primitive element.
Return the element and the computation result.
USE THIS FUNCTION WITH UNSAFE SYNC FFI CALL ONLY.
allocPrimUnsafe :: Prim a => (MBA# a -> IO b) -> IO (a, b) Source #
like withPrimUnsafe, but don't write initial value.
USE THIS FUNCTION WITH UNSAFE SYNC FFI CALL ONLY.
withPrimArray :: Prim a => PrimArray a -> (Ptr a -> Int -> IO b) -> IO b Source #
Pass primitive array to safe FFI as pointer.
Use proper pointer type and HsInt to marshall Ptr a and Int arguments
on C side.
The memory pointed by 'Ptr a' will not moved during call. After call returned,
pointer is no longer valid.
The second Int arguement is the element size not the bytes size.
Don't pass a forever loop to this function, see #14346.
Allocate a prim array and pass to FFI as pointer, freeze result into a PrimVector.
withPrimArrayUnsafe :: Prim a => PrimArray a -> (BA# a -> Int -> IO b) -> IO b Source #
Pass primitive array to unsafe FFI as pointer.
Enable UnliftedFFITypes extension in your haskell code, use proper pointer
type and HsInt to marshall ByteArray# and Int arguments on C side.
The second Int arguement is the element size not the bytes size.
USE THIS FUNCTION WITH UNSAFE SYNC FFI CALL ONLY.
allocPrimArrayUnsafe :: forall a b. Prim a => Int -> (MBA# a -> IO b) -> IO (PrimArray a, b) Source #
Allocate some bytes and pass to FFI as pointer, freeze result into a
PrimArray.
USE THIS FUNCTION WITH UNSAFE SYNC FFI CALL ONLY.
withPrimArrayList :: Prim a => [PrimArray a] -> (Ptr (Ptr a) -> Int -> IO b) -> IO b Source #
Pass primitive array list to safe FFI as pointer.
Use proper pointer type and HsInt to marshall Ptr (Ptr a) and Int
arguments on C side.
The memory pointed by 'Ptr a' will not moved during call. After call returned,
pointer is no longer valid.
The second Int arguement is the list size.
Don't pass a forever loop to this function, see #14346.
withPrimArrayListUnsafe :: [PrimArray a] -> (BAArray# a -> Int -> IO b) -> IO b Source #
Pass primitive array list to unsafe FFI as StgArrBytes**.
Enable UnliftedFFITypes extension in your haskell code, use
StgArrBytes**(>=8.10) or StgMutArrPtrs*(<8.10) pointer type and HsInt
to marshall BAArray# and Int arguments on C side.
The second Int arguement is the list size.
USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.
withForeignPtrList :: [ForeignPtr a] -> (Ptr (Ptr a) -> Int -> IO b) -> IO b Source #
Internal helpers
withMutablePrimArrayContents :: MutablePrimArray RealWorld a -> (Ptr a -> IO b) -> IO b Source #
Obtain the pointer to the content of an mutable array, and the pointer should only be used during the IO action.
This operation is only safe on pinned primitive arrays (Arrays allocated
by newPinnedPrimArray or newAlignedPinnedPrimArray).
Don't pass a forever loop to this function, see #14346.
withPrimArrayContents :: PrimArray a -> (Ptr a -> IO b) -> IO b Source #
Obtain the pointer to the content of an array, and the pointer should only be used during the IO action.
This operation is only safe on pinned primitive arrays (Arrays allocated
by newPinnedPrimArray or newAlignedPinnedPrimArray).
Don't pass a forever loop to this function, see #14346.
byteArrayContents# :: ByteArray# -> Addr# #
Intended for use with pinned arrays; otherwise very unsafe!
Re-exports
module Data.Primitive
module Control.Monad.Primitive