Segmentation fault/access violation in generated code

Ian Lynagh igloo at earth.li
Sat Jun 23 02:40:33 CEST 2012


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




More information about the Glasgow-haskell-users mailing list