Simon Peyton-Jones wrote:
> What about this specification?
> 
>         hReadByteArray :: Handle -> MutableByteArray a -> Int -> IO Int
> [...]
>         hWriteByteArray :: Handle -> MutableByteArray a -> Int -> IO ()
> [...]
> Both may block.
> 
> Would that do what you want?  If so we can add it to IOExts.

That's not what I had in mind: Given the Glorious FFI lib, Addr would
be much better than MutableByteArrays, and both are one-liners with
foreign import + Posix's read/write. What I want is

   hGetBin :: Storable a => Handle -> IO a
   hPutBin :: Storable a => Handle -> a -> IO ()

with the following "specification":

--SNIP----SNIP----SNIP----SNIP----SNIP----SNIP----SNIP----SNIP--
import IO
import IOExts(fixIO)
import FFI
import Monad(zipWithM_)

----------------------------------------------------------------------
-- cut'n'paste from 
http://www.informatik.uni-muenchen.de/~Sven.Panne/haskell_libs/ffi/Marshal.hs

marshal :: Storable a => a -> IO Addr
marshal x = do
   buf <- mallocElem x
   poke buf x
   return buf

marshalList :: Storable a => [a] -> IO (Int, Addr)
marshalList xs = do
   let numElements = length xs
   buf <- mallocElems (head xs) numElements
   zipWithM_ (pokeElemOff buf) [ 0 .. ] xs
   return (numElements, buf)

unmarshalList :: Storable a => Int -> Addr -> IO [a]
unmarshalList numElements buf =
   mapM (peekElemOff buf) [ 0 .. numElements-1 ]

inParamWith :: (a -> IO c) -> (c -> Addr) -> (c -> IO b) -> a -> IO b
inParamWith marshal_ selAddr act x = do
   marshRes <- marshal_ x
   val <- act marshRes
   free (selAddr marshRes)
   return val

inParam :: Storable a => (Addr -> IO b) -> a -> IO b
inParam = inParamWith marshal id

----------------------------------------------------------------------

-- Hmmm, this looks like a good cadidate for the Obfuscated Haskell Contest.  :-)
hGetBin :: Storable a => Handle -> IO a
hGetBin h = fixIO (\x -> inParamWith marshalList snd (peek . snd) =<< (sequence . 
replicate (sizeOf x) . hGetChar $ h))

hPutBin :: Storable a => Handle -> a -> IO ()
hPutBin h x = hPutStr h =<< inParam (unmarshalList (sizeOf x)) x

main :: IO ()
main = do
   hPutBin stdout (3.141592 :: Float)
   hPutBin stdout (12345678 :: Int)
   print =<< (hGetBin stdin :: IO Int)
--SNIP----SNIP----SNIP----SNIP----SNIP----SNIP----SNIP----SNIP--

Cheers,
   Sven
-- 
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

Reply via email to