Segmentation fault/access violation in generated code

Bas van Dijk v.dijk.bas at gmail.com
Sun Jun 17 17:11:35 CEST 2012


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/Bindings-Libusb-InitializationDeinitialization.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



More information about the Glasgow-haskell-users mailing list