I'd like to propose adding a bunch of instances for TestEquality and
TestCoercion to base and primitive types such as: IORef, STRef s, MVar as
well as MutVar and any appropriately uncoercible array types we have in
primitive.
With these you can learn about the equality of the types of elements of an
STRef when you go to
testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b)
I've been using an ad hoc versions of this on my own for some time, across
a wide array of packages, based on Atze van der Ploeg's paper:
https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by
unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness
that I get back in turn. =/
With this the notion of a "Key" introduced there can be safely modeled with
an STRef s (Proxy a).
This would make it {-# LANGUAGE Safe #-} for users to construct
heterogeneous container types that don't need Typeable information about
the values.
Implementation wise, these can either use the value equality of those
underlying primitive types and then produce a witness either by
unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce
the witness in a type-safe manner, giving us well typed core all the way
down.
-Edward
According to the FFI chapter [1] in the GHC manual, the safe FFI is useful
when you need to call a C function that can call back into haskell code. I
had always assumed that the scheduler could somehow interrupt safe FFI
calls, but the manual does not indicate this, and in some recent testing I
did in the posix library [2], I found that scheduling interrupts definitely
do not happen. With the non-threaded runtime, the following test always
hangs:
testSocketsD :: IO ()
testSocketsD = do
(a,b) <- demand =<< S.socketPair P.unix P.datagram P.defaultProtocol
_ <- forkIO $ do
bytesSent <- demand =<< S.sendByteArray b sample 0 5 mempty
when (bytesSent /= 5) (fail "testSocketsD: bytesSent was wrong")
actual <- demand =<< S.receiveByteArray a 5 mempty
actual @=? sample
sample :: ByteArray
sample = E.fromList [1,2,3,4,5]
demand :: Either Errno a -> IO a
demand = either (\e -> ioError (errnoToIOError "test" e Nothing
Nothing)) pure
In the above example, sendByteArray and receiveByteArray are safe FFI
wrappers around send and recv. It is necessary to use threadWaitRead and
threadWaitWrite before these calls to predictably get the correct behavior.
This brings to my question. In issue #34 on the github library for the unix
package [3], there is a discussion about whether to use the safe or unsafe
FFI for various POSIX system calls. On the issue there is strong consensus
that the safe FFI calls lead to better performance.
Simon Marlow writes [4] that "Unsafe foreign imports which can block for
unpredictable amounts of time cause performance problems that only emerge
when scaling to multiple cores, because they delay the GC sync. This is a
really annoying problem if it happens to you, because it's almost
impossible to diagnose, and if it happens due to an unsafe call in a
library then it's also really hard to fix."
And Gregory Collins adds that "If the call would ever block (and that
includes most filesystem functions) that means you want 'safe'."
There's something I'm definitely missing. My experience is that safe FFI
calls do not help with blocking IO (again, I've been using the non-threaded
runtime, but I doubt this makes a difference), that they only help with C
functions that call back into haskell. However, a lot of other people seem
to have a difference experience.
[1]
https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ffi-chap.ht…
[2] https://github.com/andrewthad/posix
[3] https://github.com/haskell/unix/issues/34
[4] https://github.com/haskell/unix/issues/34#issuecomment-68683424
--
-Andrew Thaddeus Martin