#3789: Segfault and -dstg-lint errors using FFI and -XEmptyDataDecls
------------------------+---------------------------------------------------
    Reporter:  judahj   |       Owner:                
        Type:  bug      |      Status:  new           
    Priority:  normal   |   Component:  Compiler (NCG)
     Version:  6.12.1   |    Keywords:                
          Os:  MacOS X  |    Testcase:                
Architecture:  x86      |     Failure:  Runtime crash 
------------------------+---------------------------------------------------
 I encountered a segfault when working with some FFI code.  I eventually
 discovered that this code also makes `-dstg-lint` complain.

 With the below files, I can reproduce the segfault and `-dstg-lint` issues
 using ghc-6.12.1 and ghc-6.10.3 on OS X 10.6.2.  The segfault goes away if
 I use -fvia-C, -O, or if I build on OS X 10.5.7.

 The segfault also goes away if I use a unit type `()` instead of
 -XEmptyDataDecls.

 {{{
 $ ghc --make test-segfault.hs foreign.c -XForeignFunctionInterface \
         -XEmptyDataDecls -fforce-recomp && ./test-segfault
 [1 of 2] Compiling Types            ( Types.hs, Types.o )
 [2 of 2] Compiling Main             ( test-segfault.hs, test-segfault.o )
 Linking test-segfault ...
 About to create...
 Segmentation fault
 }}}

 foreign.c:
 {{{
 #include <stdio.h>
 #include <stdlib.h>

 void *
 c_createFoo (int x) {
     fprintf(stderr,"Creating foo...\n");
     fflush(stderr);
     int *p = malloc(sizeof(int));
     *p = x;
     return p;
 }
 }}}
 Types.hs:
 {{{
 module Types where

 import Foreign.Ptr
 import Foreign.C.Types

 -- Replacing this line with the following one prevents the segfault,
 -- but not the -dstg-lint error.
 data Foo_
 -- type Foo_ = ()

 foreign import ccall safe c_createFoo :: CInt -> IO (Ptr Foo_)

 createFoo :: Int -> IO (Ptr Foo_)
 createFoo dtype = c_createFoo (toEnum dtype)
 }}}
 test-segfault.hs:
 {{{
 module Main where

 import Types

 main = do
     putStrLn "About to create..."
     createFoo 1
     putStrLn "Created."
 }}}

 The `-dstg-lint` error is somewhat long, but I can paste it if you're
 unable to reproduce it.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3789>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to