[Haskell-cafe] Using GHC option '-optl-static' causes segfault
Nutr1t07
nutr1t07 at outlook.com
Tue Mar 10 05:10:07 UTC 2020
It's pretty weird that program compiled with '-optl-static' runs just
well on my server Ubuntu 18.04.2 LTS (GNU/Linux 4.15.0-48-generic
x86_64), but failed running on my PC Archlinux (x86_64 Linux
5.5.8-arch1-1).
Since there are static compiling problems with glibc, why is the GHC in
stack is still built with ghlic instead of musl?
On 3/10/20 11:24 AM, Vanessa McHale wrote:
> I’ve run into that before; I think it arises because you can’t link statically against libc? In any case, trying to use network code fails with a segfault.
>
> I think it is hard to work around; you need to build GHC against musl and then use that to compile your program.
>
> Cheers,
> Vanessa
>
>> On Mar 9, 2020, at 9:32 PM, Nutr1t07 <nutr1t07 at outlook.com> wrote:
>>
>> Hi,
>>
>> I added '-optl-static' in GHC option to make my program compiled statically. When I compiled the following code using 'stack build':
>>
>> -- Main.hs
>>
>> {-# LANGUAGE OverloadedStrings #-}
>> module Main where
>>
>> import Web.Scotty as Scotty
>> import Network.Wreq as Wreq
>> import Control.Monad.IO.Class
>>
>> main :: IO ()
>> main = scotty 8443 $ do
>> Scotty.get (literal "/") $ do
>> _ <- liftIO $ Wreq.get "https://www.google.com/"
>> html "Could not see this"
>>
>> --
>>
>> Ran the compiled program and accessing "http://localhost:8443" would raise a segmentation fault.
>>
>> Here are what in my 'ghc-option':
>>
>> ghc-options:
>> - -optl-static
>> - -threaded
>> - -rtsopts
>> - -with-rtsopts=-N
>>
>> Then I removed the '-optl-static', compiled it, and the program ran well.
>>
>> It seems that it something has to do with glibc. What can I do with this problem?
>>
>> Regards
>>
>> PS. I'm using GHC 8.8.2, stack 2.1.3
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
More information about the Haskell-Cafe
mailing list