Foreign.StablePtr: nullPtr & double-free questions
Remi Turk
remi.turk at gmail.com
Sat Mar 9 03:38:50 CET 2013
Good night everyone,
I have two questions with regards to some details of the
Foreign.StablePtr module. [1]
1) The documentation suggests, but does not explicitly state, that
castStablePtrToPtr `liftM` newStablePtr x
will never yield a nullPtr. Is this guaranteed to be the case or not?
It would conveniently allow me to store a Maybe "for free", using
nullPtr for Nothing, but I am hesitant about relying on something that
isn't actually guaranteed by the documentation.
2) If I read the documentation correctly, when using StablePtr it is
actually quite difficult to avoid undefined behaviour, at least in
GHC(i). In particular, a double-free on a StablePtr yields undefined
behaviour. However, when called twice on the same value, newStablePtr
yields the same StablePtr in GHC(i).
E.g.:
module Main where
import Foreign
foo x y = do
p1 <- newStablePtr x
p2 <- newStablePtr y
print $ castStablePtrToPtr p1 == castStablePtrToPtr p2
freeStablePtr p1
freeStablePtr p2 -- potential double free!
main = let x = "Hello, world!" in foo x x -- undefined behaviour!
prints "True" under GHC(i), "False" from Hugs. Considering that foo
and main might be in different packages written by different authors,
this makes correct use rather complicated. Is this behaviour (and the
consequential undefinedness) intentional?
With kind regards,
Remi Turk
[1] http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.6.0.1/Foreign-StablePtr.html
More information about the Glasgow-haskell-users
mailing list