Segmentation fault/access violation in generated code

Bas van Dijk v.dijk.bas at gmail.com
Wed Jun 20 00:49:34 CEST 2012


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



More information about the Glasgow-haskell-users mailing list