[ Cross-mailed to ghc-users, too, because this is not really a bug ] Jan Kort wrote: > It seems that FFI no longer accepts "ByteArray Int" in ghc 4.06 > (it does in ghc 4.04), it looks intentional ? Even it is unintentional now, it will be omitted in future versions when the new FFI design is finished. > If so, is there another way to pass a String to a C function ? > [...] Of course! We (the fearless FFI task force) are not *that* evil. :-) The current state of affairs is as follows: * There has been consensus on the low-level part of the new FFI, and 4.06 comes with a new module FFI (don't forget -syslib lang) implementing the library part of it. There are no docs yet, but I'll promise to fix that "soon". Until then: "Use the source, Luke!" * There will be some changes to the GHC/Hugs-specific modules Foreign/Stable/Addr/Int/Word, some of which have already been incorporated in 4.06 (but only the ones unlikely to break any existing programs). * We still have to do some design work for the higher-level libs, which would be exactly the part needed for (un-)marshaling strings. More details can be found on http://www.informatik.uni-muenchen.de/~Sven.Panne/haskell_libs/ffi.html A *very* preliminary and incomplete version for the higher-level FFI stuff can be found there (module Marshal). Manuel Chakravarty already had some new ideas and improvements, which I was too lazy to merge into Marshal (yet). To get you going and have an easy cut'n'paste version for the common task of (un-)marshaling strings, I've specialised some functions from Marshal and extended your example with them: --------------------------------------------------------- module Main where import FFI import Monad(zipWithM_) foreign import ccall "c_test" h_test :: Addr -> IO () foreign import ccall ttyname :: Int -> IO Addr callWithString :: (Addr -> IO a) -> String -> IO a callWithString act str = do let numElements = length str buf <- mallocElems (head str) (numElements+1) zipWithM_ (pokeElemOff buf) [ 0 .. ] str pokeElemOff buf numElements '\0' val <- act buf free buf return val getStringFrom :: IO Addr -> IO String getStringFrom act = do buf <- act let loop idx accu = do x <- peekElemOff buf idx if x == '\0' then return $ reverse accu else loop (idx+1) (x:accu) loop 0 [] main :: IO() main = do callWithString h_test "test123" print =<< getStringFrom (ttyname 0) --------------------------------------------------------- Now you know, why FFI is only a *low*-level interface... :-] Cheers, Sven P.S.: Because of the readXYOffAddr bug in 4.06 discussed a few days ago, you'd better compile without -O for now. -- Sven Panne Tel.: +49/89/2178-2235 LMU, Institut fuer Informatik FAX : +49/89/2178-2211 LFE Programmier- und Modellierungssprachen Oettingenstr. 67 mailto:[EMAIL PROTECTED] D-80538 Muenchen http://www.informatik.uni-muenchen.de/~Sven.Panne