Using GHC option '-optl-static' causes segfault

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

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
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.

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
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.

Application programs can use the internal API directly, or the
While I also like static binaries, most people do not necessarily need or want them -- changing the default for GHC to be built with musl would be a huge risk, IMO. More concretely, while GHC has a maintained alpine linux package (which is based on musl), stack does not -- see https://github.com/commercialhaskell/stack/issues/2387. I've written about it a little bit (https://vadosware.io/post/static-binaries-for-haskell-a-convoluted-approach/), the post is quite old so things have likely shifted. Static linking for programs in linux is surprisingly hard (but possible with some caveats), even when you get a library linked with musl (or some other small libc) you often need to ensure that libnss is available if you're going to do dns resolutions. One alternative that looks viable is nsss (https://skarnet.org/software/nsss), but I've never actually used it -- other languages like rust and go get around this by offering domain name resolution at the language level (https://doc.rust-lang.org/std/net/trait.ToSocketAddrs.html, https://golang.org/pkg/net/#hdr-Name_Resolution). I'm not entirely sure how easy this would be to do with haskell -- is the move to make a haskell binding to nsss then using that? How easy is it to write a haskell library that will include the relevant headers that make nsss go? Here's the quick rundown on how one uses nsss: prefixed nsss_ functions directly. Most programs, however, will simply use the standard pwd.h http://pubs.opengroup.org/onlinepubs/9699919799/basedefs/pwd.h.html, grp.h http://pubs.opengroup.org/onlinepubs/9699919799/basedefs/grp.h.html or shadow.h http://man7.org/linux/man-pages/man3/getspnam.3.html interfaces. nsss provides a version of these standard headers: if an application is built with these headers, then getpwnam() will automatically be aliased to nsss_all_getpwnam(), and the other functions will be aliased similarly. Also, a cabal-based workflow might be better for building static haskell binaries -- it's normally included with containers that have the toolchain set up already like https://github.com/utdemir/ghc-musl (but as I mentioned earlier, stack is not). I *think* you could somewhat easily get stack to build a musl derived binary by using the stack docker integration (https://docs.haskellstack.org/en/stable/docker_integration/) -- again, I haven't tried this but it'd be a good subject of a blog post at some point. Victor On 3/10/20 2:10 PM, Nutr1t07 wrote:
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
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.
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.

On 3/10/20 4:24 AM, Vanessa McHale wrote:
I’ve run into that before; I think it arises because you can’t link statically against libc?
Correct, that is why I use musl for that...
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
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.
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.

On 3/10/20 4: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.
Just for clarity, this is a slightly incorrect wording: It should be "libc" -> "glibc". Other libcs (like musl) are perfectly happy to be statically linked against.

Hi,
It seems that it something has to do with glibc. What can I do with this problem?
that's right, you cannot statically link against glibc, especially not networking code, without getting crashes. Your specific issue is described on: https://github.com/nh2/static-haskell-nix/issues/17 Check out https://github.com/nh2/static-haskell-nix/#static-haskell-nix for the background and more information of how you can link statically correctly. Your current 2 choices are this (static-haskell-nix), and building in an Alpine docker container. * Stack+Docker is conceptually easier, but makes you dependent on good support for the Haskell ecosystem in Alpine, which sometimes breaks (and it is only partially under our control to fix it). * static-haskell-nix requires you to learn some nix, but allows you to override any (system) package so you have control to fix things in case things do not work (for example, if some system package is compiled without .a files you need for static linking). Finally, don't hesitate to ask me anything about it; I have spent multiple hundreds of hours on statically linking Haskell :) Niklas

Hi, On 3/10/20 5:21 PM, Niklas Hambüchen wrote:
that's right, you cannot statically link against glibc, especially not networking code, without getting crashes. Sorry to mention again, but I wonder why cannot link *especially networking code*? Because if I remove the networking part of my codes it seems to run well.

Nutr1t07
On 3/10/20 5:21 PM, Niklas Hambüchen wrote:
that's right, you cannot statically link against glibc, especially not networking code, without getting crashes. Sorry to mention again, but I wonder why cannot link *especially networking code*? Because if I remove the networking part of my codes it seems to run well.
It's because glibc's NSS (name service switch) relies on dynamic linking whatever you do. https://stackoverflow.com/questions/3430400/linux-static-linking-is-dead See also `info libc "Name Service Switch"` on a system with texinfo installed, or the corresponding node in the glibc documentation online. -- Jack

On 3/11/20 3:06 AM, Jack Kelly wrote:> It's because glibc's NSS (name service switch) relies on dynamic linking
whatever you do.
https://stackoverflow.com/questions/3430400/linux-static-linking-is-dead Another similar explanation into the same direction:
https://stackoverflow.com/questions/57476533/why-is-statically-linking-glibc...

Much thanks to /Niklas Hambüchen/, /Victor Adossi/ and everyone who helped me! I'm now using "Stack+Docker"(thanks to https://github.com/utdemir/ghc-musl) way to statically compile the code, and it looks just work as expect! I have also seen static-haskell-nix and it looks awesome but I don't know how to use nix yet so I think I should use the approach above temporarily util I learn nix or another problem arise. Thank you, Nutr1t07
participants (6)
-
Branimir Maksimovic
-
Jack Kelly
-
Niklas Hambüchen
-
Nutr1t07
-
Vanessa McHale
-
Victor Adossi