[Haskell-cafe] Why am I not allowed to use CStringLen in
foreignexport?
Brian Hulley
brianh at metamilk.com
Fri Sep 15 15:30:18 EDT 2006
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
More information about the Haskell-Cafe
mailing list