Can't allocate thunk for wcslen
Hello,
I'm trying to use the 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:
{-# 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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.2 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler (FFI) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |