[GHC] #14456: Windows runtime linker failure with icuuc
GHC
ghc-devs at haskell.org
Wed Nov 22 13:55:28 UTC 2017
#14456: Windows runtime linker failure with icuuc
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Runtime System | Version: 8.2.2
(Linker) |
Resolution: | Keywords:
Operating System: Windows | Architecture:
| Unknown/Multiple
Type of failure: GHCi crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* version: 8.2.1 => 8.2.2
Old description:
> First, install `mingw-w64-x86_64-icu` (I'm using version 58.2-2):
>
> {{{
> $ pacman -S mingw-w64-x86_64-icu
> }}}
>
> Now take this file:
>
> {{{#!hs
> module Main where
>
> import Data.Int
> import Foreign
>
> foreign import ccall "ucnv_getMaxCharSize_58"
> c_ucnv_getMaxCharSize :: Ptr () -> IO Int8
>
> main :: IO ()
> main = c_ucnv_getMaxCharSize nullPtr >>= print
> }}}
>
> GHC is able to compile this successfully:
>
> {{{
> $ ghc -licuuc Bug2.hs
> [1 of 1] Compiling Main ( Bug2.hs, Bug2.o )
> Linking Bug2.exe ...
> }}}
>
> But GHCi is unable to accomplish the same thing:
>
> {{{
> $ runghc -licuuc Bug2.hs
> ghc.exe: ^^ Could not load 'ucnv_getMaxCharSize_58', dependency
> unresolved. See top entry above.
>
> Bug2.hs:
> ByteCodeLink: can't find label
> During interactive linking, GHCi couldn't find the following symbol:
> ucnv_getMaxCharSize_58
> 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 send a bug report to:
> glasgow-haskell-bugs at haskell.org
> }}}
>
> Phyx- and I discussed this briefly on IRC. He suspected that the fact
> that `C:\Windows\System32` now contains its own copy of `icuuc.dll` is
> contributing to the issue.
New description:
First, install `mingw-w64-x86_64-icu` (I'm using version 58.2-2):
{{{
$ pacman -S mingw-w64-x86_64-icu
}}}
Now take this file:
{{{#!hs
module Main where
import Data.Int
import Foreign
import Foreign.C.String
import Foreign.C.Types
type UErrorCode = CInt
u_ZERO_ERROR :: UErrorCode
u_ZERO_ERROR = 0
foreign import ccall "ucnv_open_58"
c_ucnv_open :: CString -> Ptr UErrorCode -> IO (Ptr ())
foreign import ccall "ucnv_getMaxCharSize_58"
c_ucnv_getMaxCharSize :: Ptr () -> IO Int8
main :: IO ()
main = with u_ZERO_ERROR $ \status -> do
conv <- c_ucnv_open nullPtr status
c_ucnv_getMaxCharSize conv >>= print
}}}
GHC is able to compile this successfully:
{{{
$ ghc -licuuc Bug2.hs
[1 of 1] Compiling Main ( Bug2.hs, Bug2.o )
Linking Bug2.exe ...
$ ./Bug2.exe
1
}}}
But GHCi is unable to accomplish the same thing:
{{{
$ runghc -licuuc Bug2.hs
ghc.exe: | C:\Users\RyanGlScott\Documents\Hacking\Haskell\Bug2.o: unknown
symbol `ucnv_open_58'
Bug2.hs:
}}}
Phyx- and I discussed this briefly on IRC. He suspected that the fact that
`C:\Windows\System32` now contains its own copy of `icuuc.dll` is
contributing to the issue.
--
Comment:
Ah yes, `-llibicuuc` does indeed work with GHC HEAD. Thanks.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14456#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list