[Haskell-cafe] FFI: C-side object not destructed

Yves Parès limestrael at gmail.com
Sat Feb 26 11:59:25 CET 2011


Hello,
I'm trying to use a C++ class in Haskell through C exports.
It works all very well, except that when I call the function that deletes
the object, it is still valid, I can still call methods on it.

Here is my Haskell code:

{-# LANGUAGE ForeignFunctionInterface #-}

import Foreign
import Foreign.C.Types

newtype PKlass = PKlass (Ptr PKlass)

foreign import ccall unsafe "Klass_Create"
  kCreate :: CInt -> CInt -> IO PKlass

foreign import ccall unsafe "Klass_Destroy"
  kDestroy :: PKlass -> IO ()

foreign import ccall unsafe "Klass_GetX"
  kGetX :: PKlass -> IO CInt
foreign import ccall unsafe "Klass_GetY"
  kGetY :: PKlass -> IO CInt

foreign import ccall unsafe "Klass_AddKlass"
  kAdd :: PKlass -> PKlass -> IO PKlass


main = do
  k <- kCreate 4 5
  kDestroy k
  *kGetY k >>= print   -- This shouldn't work*
  k' <- kCreate 2 8
  k'' <- k `kAdd` k'
  kDestroy k''
  *kGetY k'' >>= print   -- This neither*


So it is very basic, and I can't understand why the supposedly destroyed
objects are still here.
Enclosed is all the source code (C++ class, C exportation and the Haskell
main hereabove).

I compile it this way:
ghc --make main.hs *.cpp -lstdc++
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110226/1251e3d0/attachment.htm>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: test.zip
Type: application/zip
Size: 1303 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110226/1251e3d0/attachment.zip>


More information about the Haskell-Cafe mailing list