RE: [Haskell-cafe] Haskell DLL crashes Excel

2006-09-25 Thread Simon Peyton-Jones
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: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] 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 .. 0x)
|  low_h :: Word8 = fromIntegral (shiftR len 8 .. 0x)
|  high_l :: Word8 = fromIntegral (shiftR len 16 .. 0x)
|  high_h :: Word8 = fromIntegral (shiftR len 24 .. 0x)
|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
| 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell DLL crashes Excel

2006-09-25 Thread Lennart Augustsson
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: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] 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 .. 0x)
|  low_h :: Word8 = fromIntegral (shiftR len 8 .. 0x)
|  high_l :: Word8 = fromIntegral (shiftR len 16 .. 0x)
|  high_h :: Word8 = fromIntegral (shiftR len 24 .. 0x)
|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
|


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell DLL crashes Excel

2006-09-22 Thread Kyra

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 .. 0x)
 low_h :: Word8 = fromIntegral (shiftR len 8 .. 0x)
 high_l :: Word8 = fromIntegral (shiftR len 16 .. 0x)
 high_h :: Word8 = fromIntegral (shiftR len 24 .. 0x)
   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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell DLL crashes Excel

2006-09-22 Thread Kyra

Kyra wrote:
Use SysAllocString... family. Also, remember they (by convention) have 
to be released from the client side.


Oops, they = such allocated BSTRs.

Cheers,
Kyra
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe