[Haskell-cafe] Haskell DLL crashes Excel

Andreas Marth Andreas-Haskell at gmx.net
Fri Sep 22 05:21:00 EDT 2006


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 <windows.h>
#include <Rts.h>

extern void __stginit_Calculate(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_Calculate);
      return TRUE;
  }
  if (reason == DLL_PROCESS_DETACH) {
      shutdownHaskell();
      return TRUE;
  }
  return TRUE;
}

----------------------------------------------------------------

And I compile the DLL with:

ghc -c --make -fglasgow-exts -static Calculate.hs
ghc -c -fglasgow-exts -static *.c
ghc --mk-dll -o Calculate.dll *.o -static -optdll--def -optdllCalculate.def

------------------------------------------------------------------

Nearly forgot Calculte.def:

LIBRARY Calculate
EXPORTS
    testL = testL at 8

-----------------------------------------------------------------

The DLL is stable regarding the length of the input string and thelength of
the return string (determined with b).
But crashes for larger(?) a's. At my computer it crashes with a >9.

There seems to be a connection between b and a. If b is 10 then a>9 crashes
a<10 is fine.
If b=1000  then a<5 is okay a>4 crashes.
If b =100 then a<5 is okay, a>5 crashes and a=5 crashes with an error
"Statement in 0x778cb032 points to 0x00000000 the function 'written' could
not be done ..." And a second one "Statement in 0x778cc441 points to
0x00000000 the function 'written' could not be done ..." (My translation of
the german errors.)


If anybody knows what is going wrong or can give me a hint how to find out
what is going wrong it would be very helpful.
Thanks Andreas



More information about the Haskell-Cafe mailing list