Haskell DLL crashes Excel

Hi everybody!
As you might now already know I try to let VBA call Haskell via a DLL. The
function returns a String. Everything works fine now if I call the function
only once. If I call it more often Excel crashes soon. Does any body have
any idea what is going wrong or how I can find out. (I am a medium skilled
Haskell user but no VBA programmer.)
My code for Haskell (Calculate.hs):
module Calculate where
import Foreign.C.String (CString, peekCString, newCString)
import Data.Word (Word8, Word16, Word32)
import Data.Bits (shiftR, (.&.))
import Foreign.Marshal.Array (newArray)
import Foreign.Ptr (Ptr, plusPtr)
type BSTR8 = Ptr Word8
createBSTR8 :: String -> IO BSTR8
createBSTR8 s = do
let
len :: Word32 = fromIntegral (length s)
low_l :: Word8 = fromIntegral (len .&. 0xFFFF)
low_h :: Word8 = fromIntegral (shiftR len 8 .&. 0xFFFF)
high_l :: Word8 = fromIntegral (shiftR len 16 .&. 0xFFFF)
high_h :: Word8 = fromIntegral (shiftR len 24 .&. 0xFFFF)
arr <- newArray ([low_l,low_h,high_l,high_h] ++ map (fromIntegral .
fromEnum) s ++ [0])
return $! plusPtr arr 4
testL :: Int -> CString -> IO BSTR8
testL n cs = do s <- peekCString cs
createBSTR8 $ concat $ take n $ repeat s
foreign export stdcall testL :: Int -> CString -> IO BSTR8
---------------------------------------------------------------
My VBA code (in Excel 2000):
Option Explicit
Dim h1 As String
Dim a As Long
Dim b As Long
Private Declare Function testL Lib "P:\Daten\Code\Calculate.dll" (ByVal n As
Long, ByVal str As String) As String
Sub Test()
a = 0
b = 10
h1 = ""
Do While a <= 15
h1 = testL(b, "What is going on here?")
a = a + 1
Debug.Print a
Debug.Print h1
Loop
End Sub
-----------------------------------------------------------
And my DllMain.c:
#include

Andreas Marth wrote:
type BSTR8 = Ptr Word8
createBSTR8 :: String -> IO BSTR8 createBSTR8 s = do let len :: Word32 = fromIntegral (length s) low_l :: Word8 = fromIntegral (len .&. 0xFFFF) low_h :: Word8 = fromIntegral (shiftR len 8 .&. 0xFFFF) high_l :: Word8 = fromIntegral (shiftR len 16 .&. 0xFFFF) high_h :: Word8 = fromIntegral (shiftR len 24 .&. 0xFFFF) arr <- newArray ([low_l,low_h,high_l,high_h] ++ map (fromIntegral . fromEnum) s ++ [0]) return $! plusPtr arr 4
Use SysAllocString... family. Also, remember they (by convention) have to be released from the client side. Cheers, Kyra

Hi Kyra! First thanks for your repeated responses. I tried to use SysAllocString as suggested by you and Esa Ilari Vuokko. Unfortuntly I get an error: "fake: undefined reference to `SysAllocString@4`" from the linker if I use "stdcall" (wich I think I should use) or fake: undefined reference to `SysAllocString`" if I use ccall. I solved this with adding C:\WINNT\system32\oleaut32.dll to the files the linker shold link. Was that correct? Because this dll crashes Excel instantly. I used the code suggested by Esa Ilari Vuokko: newtype BSTR = BSTR CWString foreign import stdcall "oleauto.h SysAllocString" c_SysAllocString :: CWString -> IO BSTR sysAllocString :: String -> IO BSTR sysAllocString s = withCWString s c_SysAllocString >>= return Added my function: testL :: Int -> CString -> IO BSTR8 testL n cs = do s <- peekCString cs sysAllocString $ concat $ take n $ repeat s foreign export stdcall testL :: Int -> CString -> IO BSTR8
Use SysAllocString... family. Also, remember they (by convention) have to be released from the client side.
Cheers, Kyra
Regarding the release from the client side: If I call a Haskell DLL from Excel shall I release the BSTR within the Haskell DLL? That would mean before the value is returned? Thanks a lot, Andreas

Andreas Marth wrote:
I solved this with adding C:\WINNT\system32\oleaut32.dll to the files the linker shold link. Was that correct? I prefer "-loleaut32" but see no big difference.
Because this dll crashes Excel instantly. I used the code suggested by Esa Ilari Vuokko:
newtype BSTR = BSTR CWString
foreign import stdcall "oleauto.h SysAllocString" c_SysAllocString :: CWString -> IO BSTR
sysAllocString :: String -> IO BSTR sysAllocString s = withCWString s c_SysAllocString >>= return Have You made your code working with no crash? Remark: ">>= return" is extraneous (but absolutely harmless) here
Regarding the release from the client side: If I call a Haskell DLL from Excel shall I release the BSTR within the Haskell DLL? That would mean before the value is returned? Nope. The rule is: if You receive some BSTR from the outside world You must release it, if You allocate some BSTR and return it to the outside world, it's the outside world's responsibility to release it.

Andreas, Nikunj, and others I don't have any experience of using GHC to build XLLs, or getting VBA to call Haskell via a DLL. However, this is something we'd like to be easy and reliable using GHC. If any of you are experts on the VBA/DLL side of the question, and can figure out what we should do to make GHC do the Right Thing, we're all ears. Meanwhile, why not document whatever you learn (even if it's provisional) on the GHC wiki? http://haskell.org/haskellwiki/GHC/Using_the_FFI That would help others. Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of | Andreas Marth | Sent: 22 September 2006 10:21 | To: haskell-cafe@haskell.org | Subject: [Haskell-cafe] Haskell DLL crashes Excel | | Hi everybody! | | As you might now already know I try to let VBA call Haskell via a DLL. The | function returns a String. Everything works fine now if I call the function | only once. If I call it more often Excel crashes soon. Does any body have | any idea what is going wrong or how I can find out. (I am a medium skilled | Haskell user but no VBA programmer.) | | My code for Haskell (Calculate.hs): | | module Calculate where | | import Foreign.C.String (CString, peekCString, newCString) | import Data.Word (Word8, Word16, Word32) | import Data.Bits (shiftR, (.&.)) | import Foreign.Marshal.Array (newArray) | import Foreign.Ptr (Ptr, plusPtr) | | type BSTR8 = Ptr Word8 | | createBSTR8 :: String -> IO BSTR8 | createBSTR8 s = do | let | len :: Word32 = fromIntegral (length s) | low_l :: Word8 = fromIntegral (len .&. 0xFFFF) | low_h :: Word8 = fromIntegral (shiftR len 8 .&. 0xFFFF) | high_l :: Word8 = fromIntegral (shiftR len 16 .&. 0xFFFF) | high_h :: Word8 = fromIntegral (shiftR len 24 .&. 0xFFFF) | arr <- newArray ([low_l,low_h,high_l,high_h] ++ map (fromIntegral . | fromEnum) s ++ [0]) | return $! plusPtr arr 4 | | | testL :: Int -> CString -> IO BSTR8 | testL n cs = do s <- peekCString cs | createBSTR8 $ concat $ take n $ repeat s | | foreign export stdcall testL :: Int -> CString -> IO BSTR8 |

I don't think GHC is to blame in this case. If you follow all the API (ABI) guidelines for building XLLs things work fine. But there's a lot of things to get right. -- Lennart On Sep 25, 2006, at 05:16 , Simon Peyton-Jones wrote:
Andreas, Nikunj, and others
I don't have any experience of using GHC to build XLLs, or getting VBA to call Haskell via a DLL. However, this is something we'd like to be easy and reliable using GHC. If any of you are experts on the VBA/DLL side of the question, and can figure out what we should do to make GHC do the Right Thing, we're all ears.
Meanwhile, why not document whatever you learn (even if it's provisional) on the GHC wiki? http://haskell.org/haskellwiki/GHC/Using_the_FFI
That would help others.
Simon
| -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of | Andreas Marth | Sent: 22 September 2006 10:21 | To: haskell-cafe@haskell.org | Subject: [Haskell-cafe] Haskell DLL crashes Excel | | Hi everybody! | | As you might now already know I try to let VBA call Haskell via a DLL. The | function returns a String. Everything works fine now if I call the function | only once. If I call it more often Excel crashes soon. Does any body have | any idea what is going wrong or how I can find out. (I am a medium skilled | Haskell user but no VBA programmer.) | | My code for Haskell (Calculate.hs): | | module Calculate where | | import Foreign.C.String (CString, peekCString, newCString) | import Data.Word (Word8, Word16, Word32) | import Data.Bits (shiftR, (.&.)) | import Foreign.Marshal.Array (newArray) | import Foreign.Ptr (Ptr, plusPtr) | | type BSTR8 = Ptr Word8 | | createBSTR8 :: String -> IO BSTR8 | createBSTR8 s = do | let | len :: Word32 = fromIntegral (length s) | low_l :: Word8 = fromIntegral (len .&. 0xFFFF) | low_h :: Word8 = fromIntegral (shiftR len 8 .&. 0xFFFF) | high_l :: Word8 = fromIntegral (shiftR len 16 .&. 0xFFFF) | high_h :: Word8 = fromIntegral (shiftR len 24 .&. 0xFFFF) | arr <- newArray ([low_l,low_h,high_l,high_h] ++ map (fromIntegral . | fromEnum) s ++ [0]) | return $! plusPtr arr 4 | | | testL :: Int -> CString -> IO BSTR8 | testL n cs = do s <- peekCString cs | createBSTR8 $ concat $ take n $ repeat s | | foreign export stdcall testL :: Int -> CString -> IO BSTR8 |
participants (4)
-
Andreas Marth
-
Kyra
-
Lennart Augustsson
-
Simon Peyton-Jones