using ghc with make

Bulat Ziganshin bulat.ziganshin at gmail.com
Wed Apr 19 08:06:49 EDT 2006


Hello Simon,

Wednesday, April 19, 2006, 12:15:55 PM, you wrote:

> It's been on my todo list for a while to benchmark the various Binary

my lib anyway will be fastest :)))

> libraries, since there's a consensus that we need some kind of Binary 
> functionality in Haskell'.

Streams library includes AltBinary functionality and also emulation of
two versions of NewBinary library - byte-aligned and bit-aligned one.
as long as you search for nhc-style serialization library (i.e., with
`get` and `put_` functions) my lib should be the best beast around. to
be exact, it was started as fast serialization library when it become
obvious that Joel Reymont's program is bound by serialization speed.
and when fast serialization routines was written, i added Streams
functionality to make this lib more useful :)

it will be great to add all these libs i written last months to GHC
and then Haskell' - AltBinary, Streams, unboxed references and
refreshed implementation of Arrays library (in particular, it supports
resizable arrays, i.e. implements one of GHC's tickets)

my problem is that i still don't documented most of these libs and
what i'm not too enthusiastic about them's cabalizing and all other
forms of maintenance. also, for Streams lib i implemented most of
things that i know how to implement, but such things as I/O
multiplexing and network support is beyond of my knowledge. btw, what
you think about network-alt lib by Einar? is it better than ghc's
bundled libs for networking? if so, i will cowork with him to add his
lib to Streams framework

> I said I'd be surprised if GHC's could be improved on.  And indeed, I am
> now surprised :-)  You do point out some places where it could be 
> improved.  The first thing I would do is replace the IOUArray with a 
> ForeignPtr now,

this will be faster only for ghc 6.6

> since that lets you unbox the Ptr without losing garbage
> collection of the memory, and retains the ability to re-allocate the 
> storage.  How does your library handle memory allocation, do you have to
> explicitly free the memory used for the buffer?

buffer handling is part of buffering stream transformer. yes, memory
freed explicitly on vClose. the AltBinary lib (and NewBinary, which is
emulated via AltBinary) just implements get/put_ for many types via
vGetByte/vPutByte, so serialization part of library don't know
anything about memory handling. btw, my lib implements even pure
(de)serialization functions - encode::a->String and decode. they just
use Streams working in ST monad - StringBuffer/StringReader

>> instance Binary Word16 where
>>   get h = do
>>     w1 <- getWord8 h
>>     w2 <- getWord8 h
>>     return $! ((fromIntegral w1 `shiftL` 8) .|. fromIntegral w2)
 >>
>> third - it's better to make all
>> operations on Int and only then pack all data to Int16 constructor

> An Int16 is represented using an Int with sign-extension, so it should
> be the same.

yes, Word8->Word16 and other conversions are handled by special rules
for `fromIntegral`. i don't looked in GHC/Word.hs when i wrote
previous letter

btw, one more drawback of ghc's Binary is what on each getWord8
operation, type of handle should be tested (whether it is file or
memory buffer). in my lib, when all operations are inlined, such test
is not required


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Glasgow-haskell-users mailing list