Binary question

alexey_rod alexey_rod@virtualisimo.net
12 Jun 2002 13:52:17 -0000


  Hi! I am using the ghc compiler for my final project and i am having
some problems. I need some amount of serialization for my project so i
decided to use drift to generate binary instances. I downloaded a port
of the binary class for ghc but i am afraid it is outdated and probably
not working correctly. My first question would be if someone has a
working version of binary for ghc 5.02.2.

  In the meantime i have a temporary version of binary but its
performance is not what i would like. Let me paste some of it
  
class Binary a where
    put :: WCarrier -> a -> IO ()
    get :: RCarrier -> IO a

data RCarrier = RCarrier {handle::Handle
			 ,byte::IORef Integer
			 ,remb::IORef Int
			 ,temp::IORef Integer}
getBits :: RCarrier -> Int -> IO Integer
getBits c w = if w == 0 then do
			     x <- readIORef . temp $ c
			     writeIORef (temp c) 0
			     return x
	      else do
		   r <- readIORef . remb $ c
		   n <- readIORef . byte $ c
		   t <- readIORef . temp $ c
		   if w <= r then do
				  let n' = n `shiftL` w .&. 255
				      r' = r - w
				      t' = t `shiftL` w + n `shiftR` (8 - w)
				  writeIORef (remb c) $! r'
				  writeIORef (byte c) $! n'
				  writeIORef (temp c) 0
				  return t'
		    else do
			let w' = w - r
			    t' = t `shiftL` r + n `shiftR` (8 - r)
			b <- hGetChar . handle $ c
			writeIORef (byte c) $! (toInteger (ord b))
			writeIORef (remb c) 8
			writeIORef (temp c) $! t'
			getBits c w'

data WCarrier = WCarrier {whandle::Handle
			 ,wbyte::IORef Integer
			 ,wremb::IORef Int}

ones n = (bit n) - 1

putBits :: WCarrier -> Int -> Integer -> IO ()
putBits (WCarrier ch cb cr) w n = f w n
    where f w n = if w == 0 then return ()
		  else do b <- readIORef cb
			  r <- readIORef cr
			  if w < r then do
					let b' = b `shiftL` w + n
					    r' = r - w
					writeIORef cb $! b'
					writeIORef cr $! r'
			   else do
				let n' = ones w' .&. n
				    b' = b `shiftL` r + (n `shiftR` w' .&. ones r)
				    w' = w - r
				hPutChar ch $! (chr (fromInteger b'))
				writeIORef cb 0
				writeIORef cr 8
				n' `seq` b' `seq` f w' n'

  My second question is how to optimize this piece of code. I suppose
that the main performance bottleneck is the use of hPutChar. I did some
profiling but some guidance will be really helpful.

  Regards,

  Alexey




-------------------------------------
Comparte e interactua con personas de tus mismos intereses en:
http://www.comunidadesweb.com