Segmentation fault/access violation in generated code

Hello, I'm trying to solve #5254 (http://hackage.haskell.org/trac/ghc/ticket/5254). The issue can be isolated to the following short program which only uses bindings-libusb (http://hackage.haskell.org/packages/archive/bindings-libusb/1.4.4.1/doc/html...): -------------------------------------------------- module Main where import Foreign import qualified Foreign.Concurrent as FC import Control.Concurrent import Bindings.Libusb.InitializationDeinitialization main :: IO () main = do ctxPtr <- alloca $ \ctxPtrPtr -> do _ <- c'libusb_init ctxPtrPtr peek ctxPtrPtr fp <- newForeignPtr p'libusb_exit ctxPtr -- fp <- FC.newForeignPtr ctxPtr $ c'libusb_exit ctxPtr threadDelay 3000000 print $ fp == fp -------------------------------------------------- When I run this program on Windows I get the following error after 3 seconds:
example.exe True Segmentation fault/access violation in generated code
The error disappears when I change the newForeignPtr line to the commented FC.newForeignPtr line. Any idea why this is happening? I don't know if it has anything to do with it but note that the libusb FFI functions are using the stdcall calling convention on Windows. I'm using GHC-7.4.2 but this error also occurs in previous versions. To reproduce this just download libusb (I recommend http://libusbx.org/) and when cabal installing bindings-libusb tell it the path to the include and library files, as in: cabal install bindings-libusb --extra-include-dirs="...\libusb\include\libusb-1.0" --extra-lib-dirs="...\libusb\MinGW32\dll" and make sure the libusb-1.0.dll is in your working directory when running the example program. Regards, Bas

I just tried building the following program with the new GHC win64_alpha1 and apart from warnings from using the unsupported stdcall calling convention running the program doesn't give a segmentation fault as it does when building the program with GHC-7.4.2: {-# LANGUAGE ForeignFunctionInterface #-} module Main where import Foreign import Foreign.C.Types main :: IO () main = do ctxPtr <- alloca $ \ctxPtrPtr -> do _ <- c'libusb_init ctxPtrPtr peek ctxPtrPtr fp <- newForeignPtr p'libusb_exit ctxPtr threadDelay 1000000 print $ fp == fp data C'libusb_context = C'libusb_context foreign import stdcall "libusb_init" c'libusb_init :: Ptr (Ptr C'libusb_context) -> IO CInt foreign import stdcall "&libusb_exit" p'libusb_exit :: FunPtr (Ptr C'libusb_context -> IO ()) Regards, Bas

Hi Bas, On Sun, Jun 17, 2012 at 05:11:35PM +0200, Bas van Dijk wrote:
module Main where
import Foreign import qualified Foreign.Concurrent as FC import Control.Concurrent import Bindings.Libusb.InitializationDeinitialization
main :: IO () main = do ctxPtr <- alloca $ \ctxPtrPtr -> do _ <- c'libusb_init ctxPtrPtr peek ctxPtrPtr
fp <- newForeignPtr p'libusb_exit ctxPtr -- fp <- FC.newForeignPtr ctxPtr $ c'libusb_exit ctxPtr
threadDelay 3000000 print $ fp == fp
What happens if you just call c'libusb_exit ctxPtr at the end, instead of using a finalizer? Are you able to reproduce this with just a .c file that is compiled and linked with the program, rather than needing libusb? That would make it easier to reproduce, to understand, and to add a test. Thanks Ian

On 23 June 2012 02:40, Ian Lynagh
Hi Bas,
On Sun, Jun 17, 2012 at 05:11:35PM +0200, Bas van Dijk wrote:
module Main where
import Foreign import qualified Foreign.Concurrent as FC import Control.Concurrent import Bindings.Libusb.InitializationDeinitialization
main :: IO () main = do ctxPtr <- alloca $ \ctxPtrPtr -> do _ <- c'libusb_init ctxPtrPtr peek ctxPtrPtr
fp <- newForeignPtr p'libusb_exit ctxPtr -- fp <- FC.newForeignPtr ctxPtr $ c'libusb_exit ctxPtr
threadDelay 3000000 print $ fp == fp
What happens if you just call c'libusb_exit ctxPtr at the end, instead of using a finalizer?
Then I don't get an error. So executing the following program with the argument "fp" gives an error (although this time I don't get an access violation but instead Windows pops up a dialog box indicating an error) and without an argument I get no error: {-# LANGUAGE ForeignFunctionInterface #-} module Main where import Foreign import Foreign.C.Types import Control.Concurrent import System.Environment main :: IO () main = do ctxPtr <- alloca $ \ctxPtrPtr -> do _ <- c'libusb_init ctxPtrPtr peek ctxPtrPtr args <- getArgs case args of ["fp"] -> do fp <- newForeignPtr p'libusb_exit ctxPtr threadDelay 1000000 print $ fp == fp _ -> c'libusb_exit ctxPtr data C'libusb_context = C'libusb_context foreign import stdcall "libusb_init" c'libusb_init :: Ptr (Ptr C'libusb_context) -> IO CInt foreign import stdcall "&libusb_exit" p'libusb_exit :: FunPtr (Ptr C'libusb_context -> IO ()) foreign import stdcall "libusb_exit" c'libusb_exit :: Ptr C'libusb_context -> IO ()
Are you able to reproduce this with just a .c file that is compiled and linked with the program, rather than needing libusb? That would make it easier to reproduce, to understand, and to add a test.
I'm not sure how to do this. I guess just copying the libusb .c and .h files to the same directory as the .hs file is not enough since libusb requires a configure phase. Regards, Bas
participants (2)
-
Bas van Dijk
-
Ian Lynagh