
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