Brian Hulley wrote:
I assume that this means that on 32 bit Windows, the format of a BSTR
is:
    Word16 -- low word of length
    Word16 -- high word of length
    Word16 -- first char of string
     ...

The above is not quite correct. It appears from http://www.oreilly.com/catalog/win32api/chapter/ch06.html that the length must preceed the actual BSTR, thus you must give VBA a pointer to the first *char* in the string not the actual start of the array of Word16's in memory. Furthermore, it appears that a terminating NULL is still needed even though the string itself can contain NULL characters. No only that, but the length must be given as the number of *bytes* (excluding the terminating NULL) not the number of characters.

Therefore here is a revised attempt at creating a Win32 BSTR:

   import Data.Word
   import Data.Bits
   import Foreign.Marshal.Array
   import Foreign.Ptr

   type BSTR = Ptr Word16

   createBSTR :: [Char] -> IO BSTR
   createBSTR s = do
       let
           len :: Word32 = fromIntegral (length s * 2)
           low :: Word16 = fromIntegral (len .&. 0xFFFF)
           high :: Word16 = fromIntegral (shiftR len 16 .&. 0xFFFF)
arr <- newArray ([low, high] ++ map (fromIntegral . fromEnum) s ++ [0])
       return $! plusPtr arr 4

   foreign export stdcall hello :: IO BSTR
   hello :: IO BSTR
   hello = createBSTR "Hello world!"

Regards, Brian.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to