#5254: usb library fails on Windows ---------------------------------+------------------------------------------ Reporter: basvandijk | Owner: Type: bug | Status: new Priority: low | Milestone: 7.6.1 Component: Compiler (FFI) | Version: 7.0.3 Keywords: | Os: Windows Architecture: Unknown/Multiple | Failure: Runtime crash Difficulty: | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------
Comment(by basvandijk): Summarizing: executing the following isolated program with the argument "fp" (for !ForeignPtr) gives an error and without it 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 () }}} Note that building the program with the new `win64_alpha1` GHC doesn't produce the error. I only get warnings that the `stdcall` calling convention is not supported. So I guess it then falls back to the `ccall` calling convention which does work. Make sure to give these flags to cabal when building the program: * `--extra-include-dirs="...\libusb\include\libusb-1.0"` * `--extra-lib-dirs="...\libusb\MinGW32\dll"` or: `--extra-lib- dirs="...\libusb\MinGW64\dll"` when building with the new `win64_alpha1` GHC. and make sure the `libusb-1.0.dll` is in your working directory when running the program. -- Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5254#comment:4> GHC <http://www.haskell.org/ghc/> The Glasgow Haskell Compiler _______________________________________________ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs