
quoth Evan Laforge
If you've ensured that iflag is a C type, then you've avoided the problem. But if, for instance, iflag was a Char, not a CChar, and you poke it into a 'char' struct field forgetting to convert to a CChar, you'll get memory corruption. I don't know if it's a common mistake, but I sure made it (very infrequently, but once is enough, in fact once is even worse), and the compiler won't tell you if you did. When I mentioned it on the list way back when no one responded, so maybe other people don't fall into that trap.
Maybe they don't! I guess it isn't so much about exactly what you were up to, but for the sake of getting to whether there's an issue here for the tutorial, I wrote up a little example program, with CChar and Char. The commented alternatives work as well, at least it looks fine to me. Notes on this: - the C struct is { char a; char b; char c; } - the Haskell T struct uses CChar, and I assert that this is the only sane option -- no storable struct for foreign use should ever have a field type like Char. - that means the Storable instance in question is CChar, and it looks to me like poke reliably writes exactly one byte in this case, whatever value is supplied (I also tried Int.) - one might very well manage to keep all the poking to t fields in the T Storable instance - that's what I'd expect the tutorial to focus on. Not that it makes any great difference, but I'm just saying that the "ypoke" function in the example is there purely for the purpose of testing that Char/CChar thing you're talking about, and would be somewhat outside what I see as core usage. Donn ------------ {-# LANGUAGE ForeignFunctionInterface #-} module Main (main) where import Foreign import Foreign.C #include "ffipokehsc.h" data T = T { taflag :: CChar , tbflag :: CChar , tcflag :: CChar } deriving Show instance Storable T where sizeOf _ = #size struct t alignment _ = alignment (undefined::CDouble) peek p = do aflag <- (#peek struct t, a) p bflag <- (#peek struct t, b) p cflag <- (#peek struct t, c) p return (T aflag bflag cflag) poke p (T aflag bflag cflag) = do (#poke struct t, a) p aflag (#poke struct t, b) p bflag (#poke struct t, c) p cflag -- ypoke :: CChar -> CChar -> CChar -> IO T ypoke :: Char -> Char -> Char -> IO T ypoke a b c = alloca $ \ tp -> do (#poke struct t, a) tp a (#poke struct t, b) tp b (#poke struct t, c) tp c peek tp -- main = ypoke 97 98 99 >>= print -- main = ypoke 'a' 'b' 'c' >>= print tptr :: T -> IO (Ptr T) tptr t = alloca $ \ pt -> do poke pt t return pt main = do p <- tptr (T 97 98 99) t <- peek p print t