[GHC] #13483: Can't allocate thunk for wcslen
GHC
ghc-devs at haskell.org
Sat Mar 25 17:25:47 UTC 2017
#13483: Can't allocate thunk for wcslen
-------------------------------------+-------------------------------------
Reporter: NickSeagull | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
(FFI) |
Keywords: | Operating System: Windows
Architecture: x86_64 | Type of failure: Compile-time
(amd64) | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Hello,
I'm trying to use the [https://sourceforge.net/projects/tinyfiledialogs
tinyfiledialogs] library through the FFI, I've put the .h and .c files in
a folder called "foreign" in the root of my project and configured cabal
so it looks in this folder. The code for calling this function is as:
{{{#!hs
{-# LANGUAGE ForeignFunctionInterface #-}
module Escri where
import Foreign.C.String
foreign import ccall "tinyfiledialogs.h tinyfd_messageBox" c_messageBox
:: CString -> CString -> CString -> CString -> Int -> IO Int
messageBox :: String -> String -> String -> String -> Int -> IO Bool
messageBox title message dialogType iconType defaultButton = do
cTitle <- newCString title
cMessage <- newCString message
cDialogType <- newCString dialogType
cIconType <- newCString iconType
result <- c_messageBox cTitle cMessage cDialogType cIconType
defaultButton
return (result == 1)
}}}
When trying to run GHCi for this project, I get the following error
{{{
Configuring GHCi with the following packages: escri
GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help
ghc.EXE: internal error: Can't allocate thunk for wcslen
(GHC version 8.0.2 for x86_64_unknown_mingw32)
Please report this as a GHC bug:
http://www.haskell.org/ghc/reportabug
This application has requested the Runtime to terminate it in an unusual
way.
Please contact the application's support team for more information.
}}}
This only happens in Windows. In OSX I just get a linker error.
If I try to make a call with stdcall, it tells:
{{{
C:\Users\Nick\Development\escri\src\Escri.hs:6:1: warning: [-Wunsupported-
calling-conventions]
* the 'stdcall' calling convention is unsupported on this platform,
treating as ccall
* When checking declaration:
foreign import stdcall safe "static tinyfiledialogs.h
tinyfd_messageBox" c_messageBox
:: CString -> CString -> CString -> CString -> Int -> IO Int
}}}
Which is strange, because I'm on Windows.
Thanks in advance.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13483>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list