[Haskell-cafe] Zlib bindings
Joel Reymont
joelr1 at gmail.com
Wed Oct 19 10:07:07 EDT 2005
Well, I just coded this. Feedback is welcome!
One thing that I found interesting is that I actually have to
allocate 4 bytes to pass the long into compress/uncompress. I thought
that I could somehow obtain the address of the Haskell variable but
this does not seem to be possible.
Thanks, Joel
--
{-# INCLUDE <zlib.h> #-}
{-# OPTIONS -fffi -fglasgow-exts #-}
module ZLib
(
compress,
uncompress
)
where
import Foreign
import Foreign.C
import Data.FastPackedString
import Prelude hiding (length)
compress :: FastString -> IO FastString
compress src = do
let src_size :: CULong = fromIntegral $ length src
dest_size :: CULong = compressBound src_size
allocaBytes (sizeOf dest_size) $ \dest_size' ->
unsafeUseAsCString src $ \src' ->
do poke dest_size' dest_size
generate (fromIntegral dest_size) $ \dest ->
do err <- compress_
dest dest_size'
(castPtr src') src_size
dest_size <- peek dest_size'
return $ fromIntegral dest_size
uncompress :: FastString -> Int -> IO FastString
uncompress src orig_size = do
let src_size :: CULong = fromIntegral $ length src
dest_size :: CULong = fromIntegral orig_size
allocaBytes (sizeOf dest_size) $ \dest_size' ->
unsafeUseAsCString src $ \src' ->
do poke dest_size' dest_size
generate (fromIntegral dest_size) $ \dest ->
do err <- uncompress_
dest dest_size'
(castPtr src') src_size
dest_size <- peek dest_size'
return $ fromIntegral dest_size
foreign import ccall unsafe "compressBound" compressBound ::
CULong -> CULong
foreign import ccall unsafe "compress" compress_ ::
Ptr Word8 -> Ptr CULong -> Ptr Word8 -> CULong -> IO CInt
foreign import ccall unsafe "uncompress" uncompress_ ::
Ptr Word8 -> Ptr CULong -> Ptr Word8 -> CULong -> IO CInt
--
http://wagerlabs.com/
More information about the Haskell-Cafe
mailing list