Problem exporting Haskell to C via a DLL in GHC 6.6
SevenThunders
mattcbro at earthlink.net
Tue Feb 6 02:35:19 EST 2007
Before I post this as a bug, I thought I'd check to make sure I'm not doing
something wrong.
For this test case, on my windows XP machine I create a simple Haskell
routine that counts the characters in a file,
create a DLL for that routine and call it from C. The C code gives the
correct answer (I think) but then
proceeds to hang and never terminate. If the readFile call is removed from
this code, and a constant output is assigned to the variable ll, the code
works fine and terminates correctly. Thus the bug may possibly be some kind
of interaction with the file IO routine, if it's a bug at all.
First the Haskell code:
baddll.hs:
module Bad
where
import Foreign.Ptr
import Foreign.C.String
import Foreign.C.Types (CInt, CDouble )
foreign export stdcall badfunc :: CString -> IO (CInt)
--
-- | Conversion from Int to CInt
mkCInt :: Int -> CInt
mkCInt n = fromIntegral n
badfunc fstr = do
file <- peekCAString fstr
sstr <- readFile file
let ll = length sstr
return $ mkCInt ll
The C code:
#include <stdio.h>
__declspec(dllimport) int __stdcall badfunc(char *outfile) ;
int main(int argc, char *argv)
{
int ll ;
ll = badfunc("bad.txt") ;
printf("ll = %d\n", ll) ;
return(1) ;
}
The .bat file used to compile everything. (Assumes ghc and MS VC++ 6.0 is
in my path)
baddll.bat:
ghc -O2 -static -c baddll.hs -fglasgow-exts
ghc -c dllBad.c
ghc --mk-dll -static -fglasgow-exts -o baddll.dll dllBad.o baddll.o
baddll_stub.o -L"." -L"." -optdll--def -optdllbaddll.def
lib /def:baddll.def /MACHINE:X86
cl baddll.c baddll.lib
The .def file used to create the dll export symbols.
baddll.def
LIBRARY baddll.dll
EXPORTS
badfunc at 4
badfunc = badfunc at 4
The boilerplate code to load and unload the Haskell runtime inside the DLL.
dllBad.c
#include <windows.h>
#include <Rts.h>
extern void __stginit_Bad(void);
static char* args[] = { "ghcDll", NULL };
/* N.B. argv arrays must end with NULL */
BOOL
STDCALL
DllMain
( HANDLE hModule
, DWORD reason
, void* reserved
)
{
if (reason == DLL_PROCESS_ATTACH) {
/* By now, the RTS DLL should have been hoisted in, but we need to
start it up. */
startupHaskell(1, args, __stginit_Bad);
return TRUE;
}
if (reason == DLL_PROCESS_DETACH) {
shutdownHaskell();
return TRUE;
}
return TRUE;
}
The text file I read in.
bad.txt:
Greetings Earthlings
If I recall correctly, from another piece of test code, this seemed to work
OK in GHC 6.4. However, I'll have to resurrect my GHC 6.4 installation to
verify this. If anyone sees an obvious problem with my code I'd love to be
informed about this.
--
View this message in context: http://www.nabble.com/Problem-exporting-Haskell-to-C-via-a-DLL-in-GHC-6.6-tf3179123.html#a8821647
Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.
More information about the Glasgow-haskell-users
mailing list