__builtin_popcountll causes linking issue on Windows
Summary
Here is a problematic project structure:
{-# LANGUAGE DeriveLift #-}
module Text (Text(..), c_bar) where
import Data.Word
import GHC.Exts
import Language.Haskell.TH.Syntax
newtype Text = Text String deriving (Eq, Show, Lift)
foreign import ccall unsafe "_hs_bar" c_bar :: Word64 -> Word64
{-# LANGUAGE TemplateHaskell #-}
module TextLift (foo) where
import Text
import Language.Haskell.TH.Syntax (lift)
foo :: Text
foo = $(lift (Text "foo"))
#include <stdint.h>
#include <stdio.h>
uint64_t _hs_bar(const uint64_t x){ return __builtin_popcountll(x); }
Steps to reproduce
Run on Windows:
git clone https://github.com/Bodigrim/ghc-linking-issue
cabal build
https://github.com/Bodigrim/ghc-linking-issue/runs/2669227937?check_suite_focus=true#step:6:14
Building library for linking-issue-0.0..
[1 of 2] Compiling Text ( Text.hs, D:\a\text\text\dist-newstyle\build\x86_64-windows\ghc-9.0.1\linking-issue-0.0\build\Text.o )
[2 of 2] Compiling TextLift ( TextLift.hs, D:\a\text\text\dist-newstyle\build\x86_64-windows\ghc-9.0.1\linking-issue-0.0\build\TextLift.o )
ghc.exe: | D:\a\text\text\dist-newstyle\build\x86_64-windows\ghc-9.0.1\linking-issue-0.0\build\Text.o: unknown symbol `_hs_bar'
ghc.exe: Could not load Object Code D:\a\text\text\dist-newstyle\build\x86_64-windows\ghc-9.0.1\linking-issue-0.0\build\Text.o.
In a different environment an error message reveals more details:
ghc.exe: | D:\a\text\text\dist-newstyle\build\x86_64-windows\ghc-9.0.1\text-1.2.4.2\build\libHStext-1.2.4.2-inplace.a: unknown symbol `__popcountdi2'
ghc.exe: | D:\a\text\text\dist-newstyle\build\x86_64-windows\ghc-9.0.1\text-1.2.4.2\build\libHStext-1.2.4.2-inplace.a: unknown symbol `_hs_text_iterN'
ghc.exe: ^^ Could not load 'textzm1zi2zi4zi2zminplace_DataziText_zdfLiftLiftedRepTextzuzdclift_closure', dependency unresolved. See top entry above.
GHC.ByteCode.Linker.lookupCE
During interactive linking, GHCi couldn't find the following symbol:
textzm1zi2zi4zi2zminplace_DataziText_zdfLiftLiftedRepTextzuzdclift_closure
This may be due to you not asking GHCi to load extra object files,
archives or DLLs needed by your current session. Restart GHCi, specifying
the missing library using the -L/path/to/object/dir and -lmissinglibname
flags, or simply by naming the relevant files on the GHCi command line.
Alternatively, this link failure might indicate a bug in GHCi.
If you suspect the latter, please report this as a GHC bug:
https://www.haskell.org/ghc/reportabug
I'm not quite sure why __builtin_popcountll
was compiled to __popcountdi2
, I'd expect __popcountti2
here, but I do not know much about this stuff.
Expected behavior
I expect a successful build.
Environment
- GHC version used: 9.0.1
- Operating System: Windows