[Haskell] How to generate a dll?
Andreas Marth
andreas-haskell at gmx.net
Sat Sep 9 14:18:15 EDT 2006
Hi!
> Hi, Andreas!
> Try adding these lines to your DllMain:
>
> if (reason == DLL_PROCESS_DETACH) {
> shutdownHaskell();
> return TRUE;
> }
>
This worked great. (At least with Excel. I didn't test it with the VB-Project yet.)
> > If I tried to return a String (marshalled to CString) the dll just plain
> > crashed when called.
> How exactly is it marshalled?
>
At the moment the test program is:
module Calculate where
import Foreign.C.String
foreign export stdcall calculate :: CString -> IO (CString)
calculate :: CString -> IO (CString)
calculate cs = do s <- peekCString cs
newCString (reverse s)
So the newCString does the marshalling. (At least I think so.)
But if I call this in VBA it crashes Excel
VBA code:
Dim helper As String
Private Declare Function calculate Lib "Calculate.dll" (ByVal x as String) As String
Sub test ()
helper = calculate("Test")
Debug.Print helper
End Sub
All really basic.
Does anybody know why that does not work?
Thanks for all the answers up to now.
Andreas
> --
> Tolik
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
--
Der GMX SmartSurfer hilft bis zu 70% Ihrer Onlinekosten zu sparen!
Ideal für Modem und ISDN: http://www.gmx.net/de/go/smartsurfer
More information about the Haskell
mailing list