stdio-0.2.0.0: A simple and high performance IO toolkit for Haskell

Copyright(c) Dong Han 2017-2018
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Std.Foreign.PrimArray

Contents

Description

This module provide functions for using PrimArray and PrimVector with GHC FFI(Foreign function interface). Since GHC runtime is garbaged collected, we have a quite complex story when passing primitive arrays to FFI. We have two types of primitive array in GHC, with the objective to minimize overall memory management cost:

  • Small primitive arrays created with newPrimArray are directly allocated on GHC heap, which can be moved by GHC garbage collector, we call these arrays unpinned. Allocating these array is cheap, we only need to check heap limit and bump heap pointer just like any other haskell heap objects. But we will pay GC cost , which is OK for small arrays.
  • Large primitive array and those created with newPinnedPrimArray are allocated on GHC managed memory blocks, which is also traced by garbage collector, but will never moved before freed, thus are called pinned. Allocating these arrays are bit more expensive since it's more like how malloc works, but we don't have to pay for GC cost.

Beside the pinned/unpinned difference, we also have two types of FFI calls in GHC:

  • Safe FFI call annotated with safe keyword. These calls are executed on separated OS thread, which can be running concurrently with GHC garbage collector, thus we want to make sure only pinned arrays are passed. The main use case for safe FFIs are long running functions, for example, doing IO polling. Since these calls are running on separated OS thread, haskell thread on original OS thread will not be affected.
  • Unsafe FFI call annotated with unsafe keyword. These calls are executed on the same OS thread which is running the haskell side FFI code, which will in turn stop GHC from doing a garbage collection. We can pass both pinned and unpinned arrays in this case. The use case for unsafe FFIs are short/small functions, which can be treated like a fat primitive operations, such as memcpy, memcmp. Using unsafe FFI with long running functions will effectively block GHC runtime thread from running any other haskell thread, which is dangerous. Even if you use threaded runtime and expect your haskell thread can be stolen by other OS thread, but this will not work since GHC garbage collector will refuse to run if one of the OS thread is blocked by FFI calls.

Base on above analysis, we have following FFI strategy table.

FFI Array pinned unpinned
unsafe directly pass directly pass
safe directly pass make a copy

In this module, we separate safe and unsafe FFI handling due to the strategy difference: if the user can guarantee the FFI are unsafe, we can save an extra copy and pinned allocation. Mistakenly using unsafe function with safe FFI will result in segfault.

For convention you should always use `Ptr a` as the tagged pointer type, and Addr as the raw address type, use `addrToPtr/ptrToAddr` to cast between them if needed.

Synopsis

Unsafe FFI

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 CSize/CSsize to marshall ByteArray# and Int arguments on C side.

The second Int arguement is the element size not the bytes size.

Don't cast ByteArray# to Addr# since the heap object offset is hard-coded in code generator: https://github.com/ghc/ghc/blob/master/compiler/codeGen/StgCmmForeign.hs#L520

In haskell side we use type system to distinguish immutable / mutable arrays, but in C side we can't. So it's users' responsibility to make sure the array content is not mutated (a const pointer type may help).

USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.

withMutablePrimArrayUnsafe :: Prim a => MutablePrimArray RealWorld a -> (MBA# a -> Int -> IO b) -> IO b Source #

Pass mutable primitive array to unsafe FFI as pointer.

The mutable version of withPrimArrayUnsafe.

USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.

withMutableByteArrayUnsafe Source #

Arguments

:: Int

In bytes

-> (MBA# Word8 -> IO b) 
-> IO b 

withPrimVectorUnsafe :: Prim a => PrimVector a -> (BA# a -> Int -> Int -> IO b) -> IO b Source #

Pass PrimVector to unsafe FFI as pointer

The PrimVector version of withPrimArrayUnsafe.

The second Int arguement is the first element offset, the third Int argument is the element length.

USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY.

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 FFI CALL ONLY.

withPrimUnsafe' :: Prim a => (MBA# a -> IO b) -> IO (a, b) Source #

Safe FFI

withPrimArraySafe :: 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 CSize/CSsize to marshall Ptr a and Int arguments on C side. The memory pointed by 'Ptr a' will not moved.

The second Int arguement is the element size not the bytes size.

Don't pass a forever loop to this function, see #14346.

withMutablePrimArraySafe :: Prim a => MutablePrimArray RealWorld a -> (Ptr a -> Int -> IO b) -> IO b Source #

Pass mutable primitive array to unsafe FFI as pointer.

The mutable version of withPrimArraySafe.

Don't pass a forever loop to this function, see #14346.

withPrimVectorSafe :: forall a b. Prim a => PrimVector a -> (Ptr a -> Int -> IO b) -> IO b Source #

Pass PrimVector to unsafe FFI as pointer

The PrimVector version of withPrimArraySafe. The Ptr is already pointed to the first element, thus no offset is provided.

Don't pass a forever loop to this function, see #14346.

withPrimSafe :: 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.

withPrimSafe' :: forall a b. Prim a => (Ptr a -> IO b) -> IO (a, b) Source #

Pointer helpers

type BA# a = ByteArray# Source #

Type alias for ByteArray#.

Since we can't newtype an unlifted type yet, type alias is the best we can get to describe a ByteArray# which we are going to pass across FFI. At C side you should use a proper const pointer type.

Don't cast BA# to Addr# since the heap object offset is hard-coded in code generator: https://github.com/ghc/ghc/blob/master/compiler/codeGen/StgCmmForeign.hs#L520

USE THIS TYPE WITH UNSAFE FFI CALL ONLY.

type MBA# a = MutableByteArray# RealWorld Source #

Type alias for MutableByteArray# RealWorld.

Since we can't newtype an unlifted type yet, type alias is the best we can get to describe a MutableByteArray# which we are going to pass across FFI. At C side you should use a proper pointer type.

Don't cast MBA# to Addr# since the heap object offset is hard-coded in code generator: https://github.com/ghc/ghc/blob/master/compiler/codeGen/StgCmmForeign.hs#L520

USE THIS TYPE WITH UNSAFE FFI CALL ONLY.

clearPtr :: Ptr a -> Int -> IO () Source #

Zero a structure.

There's no Storable or Prim constraint on a type, thus the length should be given in bytes.

addrToPtr :: Addr -> Ptr a Source #

Cast between raw address and tagged pointer.

ptrToAddr :: Ptr a -> Addr Source #

Cast between tagged pointer and raw address.

castPtr :: Ptr a -> Ptr b #

The castPtr function casts a pointer from one type to another.

re-export

module GHC.Prim