filename corruption with -osuf in ghc-7.0.3

Simon Marlow marlowsd at gmail.com
Tue Jan 3 16:30:18 CET 2012


On 24/12/2011 06:23, Evan Laforge wrote:
> I've noticed a strange behaviour with ghc's -osuf flag:
>
> % cat>Test.hs
> {-# LANGUAGE ForeignFunctionInterface #-}
> module Test where
> import Foreign
> foreign import ccall "wrapper" c_callback :: Int ->  IO (FunPtr Int)
> % ghc-7.0.3 -v -c -osuf .hs.o Test.hs
> % ls
> Tes_stub.hs.o  Test.hs        Test_stub.c
> Test.hi        Test.hs.o      Test_stub.h
>
> Notice that the .o for the _stub.c has acquired the .hs.o suffix, but
> the last 't' of 'Test' was chopped off.
>
> I tried the same test with the latest ghc-7.4, and it doesn't generate
> a Test_stub.c at all, though there is a Test_stub.h.  But I guess it
> sidesteps the question of whether -osuf should apply to the _stub.c (I
> feel like it shouldn't, since it's a c file compiled by cc, not by
> ghc).

This might be related to:

   http://hackage.haskell.org/trac/ghc/ticket/5554

Anyway, if it isn't happening with 7.4 let's not worry about it.

In 7.4 we merge the stub object file into the main object file 
automatically, so you don't have to worry about stub objects in your 
Makefiles or whatever.

Cheers,
	Simon


> I'm curious about why ghc no longer seems to need _stub.c files.  I'd
> test in more details, but runghc ghci for 7.4 is segfaulting
> unpredictably so I think there are larger problems here.
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list