
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++

Well, this code in C++ would probably work too: Klass *k = new Klass(4,5); delete k; std::cout << k->getY() << std::endl; though smart compiler would probably issue a warning. See, when you delete something, C++ doesn't automagically mark your pointer as "invalid"; in fact, it preserves all the data in your deleted class. If you didn't provide a destructor, then the only outcome of "delete" would be that the same memory can be assigned to another object by "new" operator, but it doesn't get cleared or invalidated in any way. Seems to me, Haskell works in the same way. On 26 Feb 2011, at 13:59, Yves Parès wrote:
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++
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I assume you are right.
The weirdest thing here is that getY() returns the Y value of the destructed
object while getX() returns always 0.
2011/2/26 Miguel Mitrofanov
Well, this code in C++ would probably work too:
Klass *k = new Klass(4,5); delete k; std::cout << k->getY() << std::endl;
though smart compiler would probably issue a warning. See, when you delete something, C++ doesn't automagically mark your pointer as "invalid"; in fact, it preserves all the data in your deleted class. If you didn't provide a destructor, then the only outcome of "delete" would be that the same memory can be assigned to another object by "new" operator, but it doesn't get cleared or invalidated in any way.
Seems to me, Haskell works in the same way.
On 26 Feb 2011, at 13:59, Yves Parès wrote:
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++
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, 2011-02-26 at 14:22 +0300, Miguel Mitrofanov wrote:
Well, this code in C++ would probably work too:
Klass *k = new Klass(4,5); delete k; std::cout << k->getY() << std::endl;
though smart compiler would probably issue a warning. See, when you delete something, C++ doesn't automagically mark your pointer as "invalid"; in fact, it preserves all the data in your deleted class. If you didn't provide a destructor, then the only outcome of "delete" would be that the same memory can be assigned to another object by "new" operator, but it doesn't get cleared or invalidated in any way.
Seems to me, Haskell works in the same way.
It is implementation defined (so not "C++" but "
participants (4)
-
Daniel Fischer
-
Maciej Marcin Piechotka
-
Miguel Mitrofanov
-
Yves Parès