Hello,

I am attaching files to hopefully reproduce a problem I am having. I
have not upgraded to 6.6.1 yet so let me know if it has been fixed.

$ touch fpenv_c.c fpenv.hs && cc -g -Wall -c fpenv_c.c && ghc -fasm --make 
fpenv.hs fpenv_c.o -lc
[1 of 1] Compiling Main             ( fpenv.hs, fpenv.o )
Linking fpenv ...
$ ./fpenv
(x,xFP)=(0x08090628,0x08090628)
fin_test: env=0xa7900040, p=0x808e00c
zsh: segmentation fault  ./fpenv
[139]$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6.20070420

Running in valgrind shows:

...
fin_test: env=0x437c008, p=0x1
==12777== 
==12777== Jump to the invalid address stated on the next line
==12777==    at 0x1F: ???
==12777==  Address 0x1F is not stack'd, malloc'd or (recently) free'd

I think this is when fin_test exits. I am experiencing this problem in
a much larger program, so I wrote this test case to figure out what is
going wrong. Am I using the newForeignPtrEnv API incorrectly?

Many thanks,

Frederik

-- 
http://ofb.net/~frederik/
{-# OPTIONS_GHC -ffi #-}
module Main where

import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.Marshal.Alloc
import System.Posix.Unistd

--newForeignPtrEnv :: FinalizerEnvPtr env a -> Ptr env -> Ptr a -> IO (ForeignPtr a)

foreign import ccall "null.h fin_test" finalizerTest :: FunPtr (Ptr a -> Ptr a -> IO ())

main = do
  x <- mallocBytes 5
  xFP <- newForeignPtrEnv finalizerTest (nullPtr `plusPtr` 135) x
  putStrLn $ "(x,xFP)="++show(x,xFP)
  putStrLn $ "stuff="++show(sum $ take (10^6) [1..])
  putStrLn "done"
#include <stdio.h>

void fin_test(void *env, void *p) {
  fprintf(stderr, "fin_test: env=%p, p=%p\n", env, p);
}
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to