Forcing a linking error?
Edward Z. Yang
ezyang at mit.edu
Fri Aug 14 17:51:32 UTC 2015
Omer, this ticket may be of interest to you:
https://ghc.haskell.org/trac/ghc/ticket/7790
Edward
Excerpts from Ömer Sinan Ağacan's message of 2015-08-14 03:51:49 -0700:
> Here's an example that fails with a link time error when -threaded is not used:
>
> ➜ rts_test ghc --make Main.hs
> [1 of 1] Compiling Main ( Main.hs, Main.o )
> Linking Main ...
> Main.o: In function `rn4_info':
> (.text+0x26): undefined reference to `wakeUpRts'
> collect2: error: ld returned 1 exit status
>
> With -threaded it works:
>
> ➜ rts_test ghc --make Main.hs -threaded
> Linking Main ...
>
> Code:
>
> ➜ rts_test cat Main.hs
> {-# LANGUAGE ForeignFunctionInterface #-}
>
> module Main where
>
> foreign import ccall "wakeUpRts" wakeUpRts :: IO ()
>
> main :: IO ()
> main = return ()
>
> What I did is basically I found a function in GHC RTS that is only defined when
> THREADED_RTS is defined and referred to it in my program.
>
> 2015-08-14 3:59 GMT-04:00 Erik de Castro Lopo <mle+hs at mega-nerd.com>:
> > Dear ghc-devs,
> >
> > There is a commonly used library which has at least one function
> > that when compiled into a program, requires the threaded run time
> > system. Without the threaded runtime, the program just hangs.
> >
> > One kludgy solution to this problem is to have the function check
> > for Control.Concurrent.rtsSupportsBoundThreads being true and
> > throwing an error if its not. However, it would be much nicer if
> > this could be turned into a link time error.
> >
> > Anyone have any ideas how this might be done?
> >
> > Cheers,
> > Eri
> > --
> > ----------------------------------------------------------------------
> > Erik de Castro Lopo
> > http://www.mega-nerd.com/
> > _______________________________________________
> > ghc-devs mailing list
> > ghc-devs at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
More information about the ghc-devs
mailing list