Problem exporting Haskell to C via a DLL in GHC 6.6

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

SevenThunders wrote:
Before I post this as a bug, I thought I'd check to make sure I'm not doing something wrong. 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 above *may* be the problem: it is unsafe to do anything in DllMain that may involve loading a DLL, (which therefore includes a lot of the standard platform sdk functions, some of which Haskell may need to use to start/sthurdown) because the order in which DllMain is called when Windows loads/unloads DLLs is undefined - see platform sdk docs for more info. Instead of trying to start/shutdown Haskell from DllMain, I'd export a Begin() and End() function from the DLL and explicitly call these from your application's main(). Hope this helps, Brian. -- http://www.metamilk.com

Brian Hulley wrote:
SevenThunders wrote:
Before I post this as a bug, I thought I'd check to make sure I'm not doing something wrong. 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 above *may* be the problem: it is unsafe to do anything in DllMain that may involve loading a DLL, (which therefore includes a lot of the standard platform sdk functions, some of which Haskell may need to use to start/sthurdown) because the order in which DllMain is called when Windows loads/unloads DLLs is undefined - see platform sdk docs for more info.
Instead of trying to start/shutdown Haskell from DllMain, I'd export a Begin() and End() function from the DLL and explicitly call these from your application's main().
Hope this helps, Brian. -- http://www.metamilk.com
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Interesting. Perhaps I should try that. The problem is that I found I had to add the explicit shutdown in the Dll when calling Haskell from Matlab! Apparently it would cause Matlab to crash after using the DLL. So in your scheme the Begin() would call the startupHaskell function and the End() call the shutdown Haskell? Or would the Begin initiate the linking to the specific DLL using LoadLibrary? and then End specifically unload the library; or both? Another question I have is, is it possible to create a statically linked Haskell library that can be linked using MS VC tools? Also I must say I am a bit confused about the use of the routine __stginit_Bad. Suppose I had multiple Haskell modules each with their own functions to export. Which __stginit_??? routine do I use? Thanks for the help. -- View this message in context: http://www.nabble.com/Problem-exporting-Haskell-to-C-via-a-DLL-in-GHC-6.6-tf... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.

SevenThunders wrote:
Brian Hulley wrote:
SevenThunders wrote:
DllMain if (reason == DLL_PROCESS_DETACH) { shutdownHaskell(); return TRUE; } The above *may* be the problem: it is unsafe to do anything in DllMain that...
Instead of trying to start/shutdown Haskell from DllMain, I'd export a Begin() and End() function from the DLL and explicitly call these from your application's main().
So in your scheme the Begin() would call the startupHaskell function and the End() call the shutdown Haskell?
Yes.
Or would the Begin initiate the linking to the specific DLL using LoadLibrary?
Since Begin would be a function exported by the DLL, Windows would ensure that the DLL was loaded when it is first called from your application if it was not already loaded so there would be no need for an explicit call to LoadLibrary.
and then End specifically unload the library; or both?
I wouldn't bother explicitly unloading the library - I'd leave this up to Windows. The importance of using an End function is that you can ensure that the call to shutdown Haskell happens at a time when all DLLs needed by Haskell are still available, whereas using DllMain to do the shutdown call is dangerous because DllMain may be invoked when some DLL necessary for Haskell to shutdown has already been unloaded by Windows. Ideally there would also be some way to call Begin/End when using the DLL from Matlab but I don't know anything about Matlab so can't help with this. A quick hack to enable you to use the DLL safely from your application (using Begin/End) as well as unsafely from Matlab (relying on DllMain to shutdown Haskell), would just be to have a flag in the DLL to keep track of whether you've already shut Haskell down. Then in the case for process_detach you could just check this so that shutdown would only be called from DllMain as a last resort.
Another question I have is, is it possible to create a statically linked Haskell library that can be linked using MS VC tools? Also I must say I am a bit confused about the use of the routine __stginit_Bad. Suppose I had multiple Haskell modules each with their own functions to export. Which __stginit_??? routine do I use?
I don't know - hopefully someone else may be able to answer this question. Best regards, Brian. -- http://www.metamilk.com

Brian Hulley wrote:
Since Begin would be a function exported by the DLL, Windows would ensure that the DLL was loaded when it is first called from your application if it was not already loaded so there would be no need for an explicit call to LoadLibrary.
and then End specifically unload the library; or both?
I wouldn't bother explicitly unloading the library - I'd leave this up to Windows. The importance of using an End function is that you can ensure that the call to shutdown Haskell happens at a time when all DLLs needed by Haskell are still available, whereas using DllMain to do the shutdown call is dangerous because DllMain may be invoked when some DLL necessary for Haskell to shutdown has already been unloaded by Windows.
Ideally there would also be some way to call Begin/End when using the DLL from Matlab but I don't know anything about Matlab so can't help with this. A quick hack to enable you to use the DLL safely from your application (using Begin/End) as well as unsafely from Matlab (relying on DllMain to shutdown Haskell), would just be to have a flag in the DLL to keep track of whether you've already shut Haskell down. Then in the case for process_detach you could just check this so that shutdown would only be called from DllMain as a last resort.
Another question I have is, is it possible to create a statically linked Haskell library that can be linked using MS VC tools? Also I must say I am a bit confused about the use of the routine __stginit_Bad. Suppose I had multiple Haskell modules each with their own functions to export. Which __stginit_??? routine do I use?
I don't know - hopefully someone else may be able to answer this question.
Best regards, Brian. -- http://www.metamilk.com
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
In the final analysis this seems to work fairly well. I export an End() function to Matlab that calls shutdownHaskell(). I then create a Matlab script that calls End() prior to clearing the DLL out of the namespace. Since it appears that shutdownHaskell() can be called again, even after it's already shut down without incident (at least from a few simple experiments) it works fairly robustly. All that needs to be done is to remember to use the Matlab script as needed. Meanwhile, it also appears I can call the same routines from inside C, letting windows do the DLL linkage, provided that shutdownHaskell() is NOT called when the DLL unloads as you indicated earlier. Thanks again for the help. -- View this message in context: http://www.nabble.com/Problem-exporting-Haskell-to-C-via-a-DLL-in-GHC-6.6-tf... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.

Brian, Matt | In the final analysis this seems to work fairly well. I export an End() | function to Matlab that calls | shutdownHaskell(). I then create a Matlab script that calls End() prior to | clearing the DLL out of the namespace. | Since it appears that shutdownHaskell() can be called again, even after | it's already shut down without incident (at least from a few simple | experiments) it works fairly robustly. All that needs to be done is to | remember to use the Matlab script as needed. I don't think there is any reason in principle why GHC can't generate DLLs that "just work", but plainly it's deficient at the moment. If you have now figured out what is going on, and can tell us how to improve it, do tell us. The other thing is that we could do with more "how to" documentation about GHC and DLLs. We have a bit here: http://haskell.org/haskellwiki/GHC/Using_the_FFI Could you expand it in the light of your experience? Even "here's how to make GHC play with MatLab" might be useful. Might be worth pulling out a sub-page about DLLs. I'm just keen to capture your knowledge while it's fresh! thanks Simon

Simon Peyton-Jones wrote:
I don't think there is any reason in principle why GHC can't generate DLLs that "just work", but plainly it's deficient at the moment.
The fundamental reason is that the DLL mechanism itself doesn't allow initialization/ shutdown do be hidden from the user of a DLL, because the order of loading/unloading DLLs is unspecified by the MS Windows operating system. Therefore it's not a GHC problem - it's just a fact of life with DLLs...
The other thing is that we could do with more "how to" documentation about GHC and DLLs. We have a bit here: http://haskell.org/haskellwiki/GHC/Using_the_FFI Could you expand it in the light of your experience?
I've added a section http://haskell.org/haskellwiki/GHC/Using_the_FFI#Beware_of_DllMain.28.29.21 which attempts to explain why init/exit code can't be put in DllMain, as well as an *untested* example to show what I meant by putting init/exit code in Begin/End functions instead. I've put a note next to the example to say that it's untested, and to appeal to anyone with more knowledge of static linking between Haskell and C to fix anything I've missed or replace with a better example. (Apologies for not testing it but static linking to stubs generated by GHC seems to require the DLL to be compiled by gcc and use of gcc on Windows seems to require Cygwin since gcc doesn't seem to understand Windows paths and I don't have Cygwin installed - unfortunately at the moment I don't have time to pursue this further.) Best regards, Brian. -- http://www.metamilk.com

SevenThunders wrote:
Another question I have is, is it possible to create a statically linked Haskell library that can be linked using MS VC tools? Also I must say I am a bit confused about the use of the routine __stginit_Bad. Suppose I had multiple Haskell modules each with their own functions to export. Which __stginit_??? routine do I use?
For each module, you invoke this function: void hs_add_root (void (*init_root)(void)); which you can get from HsFFI.h. eg. hs_add_root(__stginit_Foo); hs_add_root(__stginit_Bar); and you do this after calling hs_init(). Cheers, Simon

SevenThunders wrote:
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.
I wonder if you're hitting this bug: http://hackage.haskell.org/trac/ghc/ticket/926 if so, it's slightly worrying that the same thing happens if you just link your program directly to the DLL, rather than loading it explicitly. Cheers, Simon
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
__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@4 badfunc = badfunc@4
The boilerplate code to load and unload the Haskell runtime inside the DLL. dllBad.c #include
#include 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.

Simon Marlow-5 wrote:
I wonder if you're hitting this bug:
http://hackage.haskell.org/trac/ghc/ticket/926
if so, it's slightly worrying that the same thing happens if you just link your program directly to the DLL, rather than loading it explicitly.
Cheers, Simon
No doubt it is the same bug. Moreover I think even a 'direct' link to a DLL has to call some interface code that loads the DLL in the standard way during initialization. Interestingly if I follow Brian's advice and remove the shutdownHaskell call in the dllMain routine, the 'hang' goes away. Unfortunately, however, if I do this, then whenever I use the code inside Matlab and decide to clear the mex function, the dll gets unloaded and Matlab crashes. Perhaps I can expose the unloadHaskell function in some form for use in Matlab, or perhaps I should go with the Begin() and End() approach suggested earlier. I'll have to give this some thought since I use my library both inside and outside the Matlab environment. -- View this message in context: http://www.nabble.com/Problem-exporting-Haskell-to-C-via-a-DLL-in-GHC-6.6-tf... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.
participants (4)
-
Brian Hulley
-
SevenThunders
-
Simon Marlow
-
Simon Peyton-Jones