Why am I not allowed to use CStringLen in foreign export?

Hi! I try to export a Haskell function to VBA. (At the moment without COM.) Because VBA seems to expect a String with length information I tried to return a CStringLen as defined in Foreign.C.String. But if I try to compile it I get an "unacceptable argument type in foreign declaration: CStringLen". My reduced test program now is a strange "Hallo world!" program:
module Test where import Foreign.C.String
foreign export stdcall hello :: IO CStringLen hello :: IO CStringLen hello = do newCStringLen ("Hallo world!")
Do I do some thing wrong here? (If I use CString instead of CStringLen and accordingly newCString instead of newCStringLen everything compiles fine but VBA crashes.) Any help is appreciated, Andreas

Andreas Marth wrote:
Hi!
I try to export a Haskell function to VBA. (At the moment without COM.) Because VBA seems to expect a String with length information I tried to return a CStringLen as defined in Foreign.C.String. But if I try to compile it I get an "unacceptable argument type in foreign declaration: CStringLen". My reduced test program now is a strange "Hallo world!" program:
module Test where import Foreign.C.String
foreign export stdcall hello :: IO CStringLen hello :: IO CStringLen hello = do newCStringLen ("Hallo world!")
Do I do some thing wrong here? (If I use CString instead of CStringLen and accordingly newCString instead of newCStringLen everything compiles fine but VBA crashes.)
The FFI only supports a very limited range of types. CString is supported because it is just defined by: type CString = Ptr CChar whereas CStringLen is defined as (Ptr CChar, Int) and tuples can't be passed through the FFI. In any case, the BSTR type required by VBA is not so simple as a CStringLen.
From the Microsoft Platfrom SDK docs,
BSTRs are wide, double-byte (Unicode) strings on 32-bit Windows platforms and narrow, single-byte strings on the AppleĀ® PowerMacT. The length is stored as an integer at the memory location preceding the data in the string. 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 ... so you could try creating an array of Word16's in that format and passing them, perhaps something like: 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) low :: Word16 = fromIntegral (len .&. 0xFFFF) high :: Word16 = fromIntegral (shiftR len 16 .&. 0xFFFF) newArray ([low, high] ++ map (fromIntegral . fromEnum) s) foreign export stdcall hello :: IO BSTR hello :: IO BSTR hello = createBSTR "Hello world!" (The above code compiles but is untested) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

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.

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
Thanks a lot for this information it helped a lot.
Because I use the VBA 6 version the string characters are supposed to be a
byte so I changed your code to
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
Maybe this helps some one else too.
I am thinking about creating a wikipage about Haskell<->VBA interfacing
through a DLL.
Is it okay for you if I put your code there?
I am a bit concerned about the memory. newArray states that the memory has
to be freed after usage. Is this needed here? How can it be done?
Thanks to everyone who responded,
Andreas
----- Original Message -----
From: "Brian Hulley"
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.

Andreas Marth wrote:
Thanks a lot for this information it helped a lot.
Glad to be of help.
I am thinking about creating a wikipage about Haskell<->VBA interfacing through a DLL. Is it okay for you if I put your code there?
Yes.
I am a bit concerned about the memory. newArray states that the memory has to be freed after usage. Is this needed here? How can it be done?
One way could be to write a function which creates the BSTR, passes it to a function, then deallocates the BSTR before returning eg (untested): import Control.Exception (bracket) withBSTR8 :: [Char] -> (BSTR8 -> IO a) -> IO a withBSTR8 s f = bracket (createBSTR8 s) (\bstr -> free (bstr `plusPtr` (-4))) (\bstr -> f bstr) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Hello Brian, Friday, September 22, 2006, 9:03:01 PM, you wrote:
withBSTR8 :: [Char] -> (BSTR8 -> IO a) -> IO a withBSTR8 s f = bracket (createBSTR8 s) (\bstr -> free (bstr `plusPtr` (-4))) (\bstr -> f bstr)
this may be shortened to
withBSTR8 s = bracket (createBSTR8 s) (\bstr -> free (bstr `plusPtr` (-4)))
my lib contains a tons of such brackets -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Andreas Marth wrote:
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)
Hi - I just noticed the mask should be changed to 0xFF for the BSTR8 version above. Also, I'm not actually sure if a mask is needed at all. I just used one to make sure there would be no chance of an overflow exception being thrown, but the Haskell report doesn't seem to specify anything at all about the behaviour of (fromIntegral) when converting between types of different sizes. Perhaps someone on the list can clarify whether or not a mask is needed ie is fromIntegral allowed to throw exceptions or does it always just silently discard unwanted bits of the argument being converted? Thanks, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com
participants (3)
-
Andreas Marth
-
Brian Hulley
-
Bulat Ziganshin