Adding binary to the Haskell Platform

Here's a ticket for Simon Marlow's proposal: http://trac.haskell.org/haskell-platform/ticket/86 Let's discuss, then have the steering committee recommend yay/nay. -- Don

The binary package is too lazy and in some cases the decoding dies
with "stack overflow". At least this was the situation the last time
when I tried to use it. Since then I am using hacked version which is
stricter. This should be addressed before to add this package to the
platform.
Another problem that I see is that Int is serialized as 64 bit
integer. This makes the serialized data too large. The Int type is
also used internally, for example to store the length of a list, the
size of a map, etc, so you can't avoid the problem by using custom
putInt function. In fact the binary representation is so verbose that
sometimes it is more compact to use textual representation. In my
hacked version I use serialization for integers which use variable
number of bytes. If someone wants to store 64 bit integer then he/she
could always use Int64. I know that the binary package could be
combined with gzip to make the data more compact but this is
unnecessary overhead.
Krasimir
On 8/5/09, Don Stewart
Here's a ticket for Simon Marlow's proposal:
http://trac.haskell.org/haskell-platform/ticket/86
Let's discuss, then have the steering committee recommend yay/nay.
-- Don _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Wed, Aug 5, 2009 at 01:15, Krasimir Angelov
The binary package is too lazy and in some cases the decoding dies with "stack overflow". At least this was the situation the last time when I tried to use it. Since then I am using hacked version which is stricter. This should be addressed before to add this package to the platform.
Not all encodings are right for everyone. IIRC, many complaints about binary are due to overflows when encoding/decoding large maps or lists. This is because of the [] instance. I, myself, have been bitten by this, but I don't think it's a flaw in the library -- there are plenty of people using the library who haven't complained about the instance. If the instance isn't right for you, write a new one. That's what I did. Denis

On Wed, Aug 05, 2009 at 06:48:02AM -0600, Denis Bueno wrote:
[...] This is because of the [] instance. I, myself, have been bitten by this, but I don't think it's a flaw in the library -- there are plenty of people using the library who haven't complained about the instance.
If the instance isn't right for you, write a new one. That's what I did.
The problem is that people shouldn't be reinventing the wheel everytime. I propose adding something along the lines of this snippet to binary (untested): import Control.Applicative import Control.Monad (replicateM_) -- | Provides a new instance of 'Binary' to lists that 'put's and -- 'get's using chunks instead of forcing the whole spine of -- the list before writing the first byte. This enconding is -- less space-efficient in the disk, though, having an overhead -- of @1 + (length xs `div` 255)@ bytes instead of only four -- bytes (independently of list size), the overhead of the -- default instance. newtype Chunked a = Chunked {unChunked :: [a]} instance Binary (Chunked a) where -- This 'put' should be good enough. put = mapM_ putChunk . chunks 255 . unChunked where chunks 255 [] = [(0,[])] -- not []! chunks _ [] = [] chunks _ xs = let (i,f) = splitAt 255 xs len = length i in (len,i) : chunks len f putChunk (len,xs) = putWord8 len >> mapM_ put xs -- I don't know if this get works nicely, though. get = getWord8 >>= go [] where go acc 0 = return $ concat $ reverse acc go acc len = do xs <- replicateM_ len get len' <- if len == 255 then getWord8 else return 0 go (xs:acc) len' -- Felipe.

Hi
Since we're pointing out flaws in Data.Binary, I might as well add mine too :-)
I found that encode/decode of a String was massively slower than
serialising a String which I converted to a bytestring on the way in
and on the way out. They are exactly equivalent (at the binary
representation and the interface level), but String is clearly
inefficient. I also noticed that for String one way round was far
slower than the other, I think decoding was much slower, which was
surprising since encoding should have to do more work (length calls
etc)
Unfortunatley I got busy with work and never managed to write all the
details down, but this might be a good place to start benchmarking.
Thanks
Neil
On Wed, Aug 5, 2009 at 2:23 PM, Felipe Lessa
On Wed, Aug 05, 2009 at 06:48:02AM -0600, Denis Bueno wrote:
[...] This is because of the [] instance. I, myself, have been bitten by this, but I don't think it's a flaw in the library -- there are plenty of people using the library who haven't complained about the instance.
If the instance isn't right for you, write a new one. That's what I did.
The problem is that people shouldn't be reinventing the wheel everytime. I propose adding something along the lines of this snippet to binary (untested):
import Control.Applicative import Control.Monad (replicateM_)
-- | Provides a new instance of 'Binary' to lists that 'put's and -- 'get's using chunks instead of forcing the whole spine of -- the list before writing the first byte. This enconding is -- less space-efficient in the disk, though, having an overhead -- of @1 + (length xs `div` 255)@ bytes instead of only four -- bytes (independently of list size), the overhead of the -- default instance. newtype Chunked a = Chunked {unChunked :: [a]}
instance Binary (Chunked a) where -- This 'put' should be good enough. put = mapM_ putChunk . chunks 255 . unChunked where chunks 255 [] = [(0,[])] -- not []! chunks _ [] = [] chunks _ xs = let (i,f) = splitAt 255 xs len = length i in (len,i) : chunks len f putChunk (len,xs) = putWord8 len >> mapM_ put xs
-- I don't know if this get works nicely, though. get = getWord8 >>= go [] where go acc 0 = return $ concat $ reverse acc go acc len = do xs <- replicateM_ len get len' <- if len == 255 then getWord8 else return 0 go (xs:acc) len'
-- Felipe. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

kr.angelov:
The binary package is too lazy and in some cases the decoding dies with "stack overflow". At least this was the situation the last time when I tried to use it. Since then I am using hacked version which is stricter. This should be addressed before to add this package to the platform.
The stack overflow with [a] was fixed a few months ago. I'd be interested to know if there were other issues with instances.
Another problem that I see is that Int is serialized as 64 bit integer. This makes the serialized data too large. The Int type is also used internally, for example to store the length of a list, the size of a map, etc, so you can't avoid the problem by using custom putInt function. In fact the binary representation is so verbose that sometimes it is more compact to use textual representation. In my hacked version I use serialization for integers which use variable number of bytes. If someone wants to store 64 bit integer then he/she could always use Int64. I know that the binary package could be combined with gzip to make the data more compact but this is unnecessary overhead.
For this, we recommend the lazy zlib library to compress as you see fit. -- Don

Ok. I tried to replace my hacked version of Data.Binary with the latest version of the library. Indeed the stack overflow error is fixed. I did some further experiments: 1. After upgrading I tried to compare the two implementations. First I was surprised to find that my version of binary is 3-4 times slower than the latest official version. After some experiments I found that the problem was in my version of Data.Binary.Get.getWord8. In the official release it is: getWord8 :: Get Word8 getWord8 = getPtr (sizeOf (undefined :: Word8)) while in my version it was: getWord8 = do S s ss bytes <- get case B.uncons s of Just (w,rest) -> do put $! S rest ss (bytes + 1) return $! w Nothing -> case L.uncons ss of Just (w,rest) -> do put $! mkState rest (bytes + 1) return $! w Nothing -> fail "too few bytes" I don't remember why I had changed it but probably it was an attempt to make it faster since I use getWord8 often. I don't know what had changed but now fist version is much much faster. When I reverted to using the fist version my library become as fast as the official binary library. 2. I tried to revert the implementation of the Get monad from strict to lazy. This made the decoding even faster - from 1.52 sec to 1.08 sec for ~ 3 Mb of data. Good achievement. 3. After the above changes the only differences between my version and the official version are that I have different instance for Int. The impact is that with my instance the output is from 2 to 4 times more compact. As a consequence the decoding is also faster with about 50%. I know that I can use compression to reduce the size of the output but this will make the deserialization only slower, not faster. Why it is so important to store Int as Int64 instead of as variable bytes field? This only adds extra overhead. Regards, Krasimir

Krasimir Angelov wrote:
I know that I can use compression to reduce the size of the output but this will make the deserialization only slower, not faster.
Couldn't the binary package try to create a ByteString with maximal sharing directly? I.e. every ByteString gets an index, which is marked and used, whenever the index is shorter (as ByteString) than the ByteString it stands for. (A similar approach is used for shared ATerms, ie. see http://www.haskell.org/pipermail/glasgow-haskell-users/2005-December/009485....) Wouldn't that be faster than the separate compression and decompression phases and faster than reading and writing such large files? Cheers Christian

Let's discuss, then have the steering committee recommend yay/nay.
We should have _some_ kind of binary library in the Platform, but I don't know whether the proposed library is the right one. In a recent application, I found Data.Binary very slow, both to encode and to decode data. Decoding had stack-overflows, and when I increased the stack, it took about 20mins to read in an 8Mb file. When I then turned on optimisation with -O, the performance improved considerably (down to ~30secs to read the same file). This was using the standard instances of Binary for data structures like Data.Map. 30secs was still too slow, so we ended up needing to write our own improved instance for Data.Map. (Timings were similar with both ghc-6.8.3 and ghc-6.10.3.) Regards, Malcolm

The stricter version of Data.Binary is here:
http://code.haskell.org/gf/src/Data
It avoids the stack overflow and *might* be faster.
On 8/5/09, Malcolm Wallace
Let's discuss, then have the steering committee recommend yay/nay.
We should have _some_ kind of binary library in the Platform, but I don't know whether the proposed library is the right one.
In a recent application, I found Data.Binary very slow, both to encode and to decode data. Decoding had stack-overflows, and when I increased the stack, it took about 20mins to read in an 8Mb file. When I then turned on optimisation with -O, the performance improved considerably (down to ~30secs to read the same file). This was using the standard instances of Binary for data structures like Data.Map. 30secs was still too slow, so we ended up needing to write our own improved instance for Data.Map. (Timings were similar with both ghc-6.8.3 and ghc-6.10.3.)
Regards, Malcolm
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 05/08/2009 08:44, Malcolm Wallace wrote:
Let's discuss, then have the steering committee recommend yay/nay.
We should have _some_ kind of binary library in the Platform, but I don't know whether the proposed library is the right one.
In a recent application, I found Data.Binary very slow, both to encode and to decode data. Decoding had stack-overflows, and when I increased the stack, it took about 20mins to read in an 8Mb file. When I then turned on optimisation with -O, the performance improved considerably (down to ~30secs to read the same file). This was using the standard instances of Binary for data structures like Data.Map. 30secs was still too slow, so we ended up needing to write our own improved instance for Data.Map. (Timings were similar with both ghc-6.8.3 and ghc-6.10.3.)
Ok, the way to proceed is to build a set of benchmarks. I did some rough timings myself recently, and found that binary was roughly comparable to the Binary module in GHC, which as far as I know is fairly fast (though I know there are faster libraries out there). I suspect we're all measuring different things. Would someone like to work on benchmarking binary and identifying the weak points? Cheers, Simon

marlowsd:
Ok, the way to proceed is to build a set of benchmarks. I did some rough timings myself recently, and found that binary was roughly comparable to the Binary module in GHC, which as far as I know is fairly fast (though I know there are faster libraries out there).
I suspect we're all measuring different things. Would someone like to work on benchmarking binary and identifying the weak points?
I'll benchmark the default instances, and the underlying primitives. Let's see what that shows up. -- Don

malcolm.wallace:
Let's discuss, then have the steering committee recommend yay/nay.
We should have _some_ kind of binary library in the Platform, but I don't know whether the proposed library is the right one.
In a recent application, I found Data.Binary very slow, both to encode and to decode data. Decoding had stack-overflows, and when I increased the stack, it took about 20mins to read in an 8Mb file. When I then turned on optimisation with -O, the performance improved considerably (down to ~30secs to read the same file). This was using the standard instances of Binary for data structures like Data.Map. 30secs was still too slow, so we ended up needing to write our own improved instance for Data.Map. (Timings were similar with both ghc-6.8.3 and ghc-6.10.3.)
I don't think I've ever benchmarked without optimizations. Unfortunately, as Data.Map is exported abstractly, we can't use the internal folds as we do for the Data.Sequence instance. Can you submit your improved Map instance? In general, Data.Binary is heavily optimized for the underlying Get/Put monads, but instances for different data types are just straight forward implementations (which seems to be what people complain about the most: very large lists (in the past) and very large Data.Maps). -- Don

On Tue, Aug 4, 2009 at 3:55 PM, Don Stewart
Here's a ticket for Simon Marlow's proposal:
http://trac.haskell.org/haskell-platform/ticket/86
Let's discuss, then have the steering committee recommend yay/nay.
-- Don _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
To add to the laundry list of problems with Data.Binary, I don't like the fact that decode calls error on invalid input. I can't think of any great alternatives (using Maybe as the result type would be too strict, of course, and returning partial results would be difficult with polymorphism), but it seems a bit unclean that decode has to be used with the IO monad to catch the errors. (Of course, the only reason you would have bad input would be if you were using the IO monad, so the practical implications are not great, but still, it would be nice if there was a better way.) Alex

alexander.dunlap:
To add to the laundry list of problems with Data.Binary, I don't like the fact that decode calls error on invalid input. I can't think of any great alternatives (using Maybe as the result type would be too strict, of course, and returning partial results would be difficult with polymorphism), but it seems a bit unclean that decode has to be used with the IO monad to catch the errors. (Of course, the only reason you would have bad input would be if you were using the IO monad, so the practical implications are not great, but still, it would be nice if there was a better way.)
That's right. Originally, it used a custom Either type, but it isn't possible to stream decoders that way. I'd consider it an intentional design feature. -- Don

On Wed, Aug 5, 2009 at 1:34 PM, Don Stewart
alexander.dunlap:
To add to the laundry list of problems with Data.Binary, I don't like the fact that decode calls error on invalid input. I can't think of any great alternatives (using Maybe as the result type would be too strict, of course, and returning partial results would be difficult with polymorphism), but it seems a bit unclean that decode has to be used with the IO monad to catch the errors. (Of course, the only reason you would have bad input would be if you were using the IO monad, so the practical implications are not great, but still, it would be nice if there was a better way.)
That's right. Originally, it used a custom Either type, but it isn't possible to stream decoders that way.
I'd consider it an intentional design feature.
-- Don
OK. Would it be worth creating an extensible exception (something like BinaryDecodeError) for this then, instead of using the call to error? That would at least make it less error-prone to catch. Alex

alexander.dunlap:
On Wed, Aug 5, 2009 at 1:34 PM, Don Stewart
wrote: alexander.dunlap:
To add to the laundry list of problems with Data.Binary, I don't like the fact that decode calls error on invalid input. I can't think of any great alternatives (using Maybe as the result type would be too strict, of course, and returning partial results would be difficult with polymorphism), but it seems a bit unclean that decode has to be used with the IO monad to catch the errors. (Of course, the only reason you would have bad input would be if you were using the IO monad, so the practical implications are not great, but still, it would be nice if there was a better way.)
That's right. Originally, it used a custom Either type, but it isn't possible to stream decoders that way.
I'd consider it an intentional design feature.
-- Don
OK. Would it be worth creating an extensible exception (something like BinaryDecodeError) for this then, instead of using the call to error? That would at least make it less error-prone to catch.
I think that would be a good idea. Showing how to catch it in the documentation. I'm wary of breaking the 70 packages that use Data.Binary for this, rather, add this as a list of API changes for the next major release. -- Don

On Wed, Aug 05, 2009 at 01:47:07PM -0700, Donald Bruce Stewart wrote:
alexander.dunlap:
OK. Would it be worth creating an extensible exception (something like BinaryDecodeError) for this then, instead of using the call to error? That would at least make it less error-prone to catch.
I think that would be a good idea. Showing how to catch it in the documentation.
I'm wary of breaking the 70 packages that use Data.Binary for this, rather, add this as a list of API changes for the next major release.
If you're planning a change that you are worried would break users of the package, wouldn't it be better to do it before putting it into the platform? Or have I misunderstood what you meant? Thanks Ian

igloo:
On Wed, Aug 05, 2009 at 01:47:07PM -0700, Donald Bruce Stewart wrote:
alexander.dunlap:
OK. Would it be worth creating an extensible exception (something like BinaryDecodeError) for this then, instead of using the call to error? That would at least make it less error-prone to catch.
I think that would be a good idea. Showing how to catch it in the documentation.
I'm wary of breaking the 70 packages that use Data.Binary for this, rather, add this as a list of API changes for the next major release.
If you're planning a change that you are worried would break users of the package, wouldn't it be better to do it before putting it into the platform?
Or have I misunderstood what you meant?
So two things: 1. We can do API-breaking changes in the platform on major releases. 2. When new packages come in, I'm wary of breaking their APIs as established prior to them being added, as then the platform release that includes them is not usable as a platform for those existing packages. Maybe 2 is not a valid concern. Maybe the HP inclusion is the time to break things. But maybe we won't then add popular packages -- because changing their APIs as requested would break too many things :/ This is the tension between "blessed" (small set of perfectionist libs) and "comprehensive" (large set of not-quite-perfect useful libs). And I'm somewhat concerned we're only focusing on the blessedness -- things being perfect -- rather than the comprehensiveness : things being useful and widely used. Do we need a policy decision: * will the Platform Steering Committee make inclusion conditional on API changes? Is that something we want to do? Maybe we just decide on a case-by-case basis. -- Don

On Wed, Aug 05, 2009 at 02:24:09PM -0700, Donald Bruce Stewart wrote:
igloo:
On Wed, Aug 05, 2009 at 01:47:07PM -0700, Donald Bruce Stewart wrote:
alexander.dunlap:
OK. Would it be worth creating an extensible exception (something like BinaryDecodeError) for this then, instead of using the call to error? That would at least make it less error-prone to catch.
I think that would be a good idea. Showing how to catch it in the documentation.
I'm wary of breaking the 70 packages that use Data.Binary for this, rather, add this as a list of API changes for the next major release.
If you're planning a change that you are worried would break users of the package, wouldn't it be better to do it before putting it into the platform?
Or have I misunderstood what you meant?
So two things:
1. We can do API-breaking changes in the platform on major releases.
2. When new packages come in, I'm wary of breaking their APIs as established prior to them being added, as then the platform release that includes them is not usable as a platform for those existing packages.
I don't understand how adding newapi in HPv2 is worse than adding oldapi in HPv2 replacing it with newapi in HPv3 Either way, when you put newapi in the HP there will be a period where other packages need to catch up with the changes. I'm not opposed to changing APIs in the platform, and if it would take a long time to design, implement and test a planned API change then I wouldn't see a problem with adding an oldapi in the mean time (assuming oldapi is "good enough").
Maybe 2 is not a valid concern. Maybe the HP inclusion is the time to break things. But maybe we won't then add popular packages -- because changing their APIs as requested would break too many things :/
I think we have to be willing to break things, or we will become obsolete. There is a balance between stability and progress, of course. Thanks Ian

Ian Lynagh wrote:
Donald Bruce Stewart wrote:
So two things:
1. We can do API-breaking changes in the platform on major releases.
2. When new packages come in, I'm wary of breaking their APIs as established prior to them being added, as then the platform release that includes them is not usable as a platform for those existing packages.
I don't understand how adding newapi in HPv2 is worse than adding oldapi in HPv2 replacing it with newapi in HPv3
Either way, when you put newapi in the HP there will be a period where other packages need to catch up with the changes.
The difference is this: If we follow the former (API before HP) then people who need to debug the upgrade process will have to switch back and forth between HP vs raw Cabal, which could be a nightmare. If we follow the latter (HP before API) then developers will only need to toggle between different HP versions, which would be a lot easier to setup in most environments. I think the HP-before-API path is more likely to keep us agile since it makes the API breaking changes easier to fix. However, it does have the downside of including known "broken" packages in the HP, even if only for a little while. The question is, how much do we want the HP to serve as a migration path? If expected breakage is small, then the API changes should probably come before HP inclusion. If the expected breakage is large ---as it will be for any popular package--- then it may be good to have an initial HP which solidifies the "classic" interface so that unknown and one-off projects, which may not be maintained, can still make use of the old API as well as the benefits of the HP. That is, there's some benefit in providing snapshots of the community as it is, rather than the ideal of what we would like. The question is the extent to which this is the HP's job. We do already have Cabal and Hackage which would allow users to install old versions of packages, so the benefits would be in the one-click install as well as capturing the in-time correlations between different packages (which Hackage doesn't currently provide a nice interface for). Providing semi-blessed packages in the HP before changing APIs could help improve buy in, and will reduce the disturbance of adding new packages, but it also increases the instability for end users since there will be more API changes within the HP track.
Maybe 2 is not a valid concern. Maybe the HP inclusion is the time to break things. But maybe we won't then add popular packages -- because changing their APIs as requested would break too many things :/
I think we have to be willing to break things, or we will become obsolete. There is a balance between stability and progress, of course.
I'd say that stability is actually the balance between legacy and progress. Ironically, Hackage serves both legacy and progress, since it gives access to old versions and GHC is able to switch between different versions of packages. From that perspective, the HP serves as the balance, providing a stable subset of Hackage. This is a rather unique arrangement since most package trees conflate the recording of history and the stable image of it. The question remains, how closely should the fulcrum follow the growing edge? -- Live well, ~wren

On Wed, Aug 5, 2009 at 10:47 PM, Don Stewart
alexander.dunlap:
On Wed, Aug 5, 2009 at 1:34 PM, Don Stewart
wrote: alexander.dunlap:
To add to the laundry list of problems with Data.Binary, I don't like the fact that decode calls error on invalid input. I can't think of any great alternatives (using Maybe as the result type would be too strict, of course, and returning partial results would be difficult with polymorphism), but it seems a bit unclean that decode has to be used with the IO monad to catch the errors. (Of course, the only reason you would have bad input would be if you were using the IO monad, so the practical implications are not great, but still, it would be nice if there was a better way.)
That's right. Originally, it used a custom Either type, but it isn't possible to stream decoders that way.
I'd consider it an intentional design feature.
-- Don
OK. Would it be worth creating an extensible exception (something like BinaryDecodeError) for this then, instead of using the call to error? That would at least make it less error-prone to catch.
I think that would be a good idea. Showing how to catch it in the documentation.
I'm wary of breaking the 70 packages that use Data.Binary for this, rather, add this as a list of API changes for the next major release.
Would this really break that many libraries? Are there many libraries that catch the exception that can be raised by error? Cheers, Johan

johan.tibell:
I'm wary of breaking the 70 packages that use Data.Binary for this, rather, add this as a list of API changes for the next major release.
Would this really break that many libraries? Are there many libraries that catch the exception that can be raised by error?
Ah! Good question -- maybe we can find out... by building Hackage!

On Thu, Aug 6, 2009 at 8:48 AM, Don Stewart
johan.tibell:
I'm wary of breaking the 70 packages that use Data.Binary for this, rather, add this as a list of API changes for the next major release.
Would this really break that many libraries? Are there many libraries that catch the exception that can be raised by error?
Ah! Good question -- maybe we can find out... by building Hackage!
While I agree with the general sentiment I don't think that would work in this case as the thrown exception isn't part of the type. -- Johan

That's right. Originally, it used a custom Either type, but it isn't possible to stream decoders that way.
What about this: you could return a pair (Result,Error). By forcing the Result you get an exception if there is an error. You can check the Error always without risk of exception. Cheers, JP.

Don Stewart wrote:
Here's a ticket for Simon Marlow's proposal:
http://trac.haskell.org/haskell-platform/ticket/86
Let's discuss, then have the steering committee recommend yay/nay.
In http://www.haskell.org/pipermail/libraries/2009-July/012139.html, Duncan said:
It is not the intention that the committee members get much more say in policy decisions than other active contributors to discussion on the libraries mailing list. We hope therefore that the membership of the committee does not need to be terribly formal. The only difficulty comes when consensus cannot be reached on an issue where making some decision is widely agreed to be better than making no decision. There is no specified protocol for this situation at this stage.
So I'm a bit confused about what the purpose of the steering committee's recommendation would be. Would it amount to a decision about inclusion, or an expression of their opinion in the hope of guiding the community towards a consensus, or something else? The first choice contradicts what Duncan said was the role of the committee, while the second doesn't seem any more worthwhile than individual members expressing their own opinions separately. Cheers, Ganesh =============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ===============================================================================

On Thu, 2009-08-06 at 10:22 +0100, Sittampalam, Ganesh wrote:
Don Stewart wrote:
Here's a ticket for Simon Marlow's proposal:
http://trac.haskell.org/haskell-platform/ticket/86
Let's discuss, then have the steering committee recommend yay/nay.
In http://www.haskell.org/pipermail/libraries/2009-July/012139.html, Duncan said:
It is not the intention that the committee members get much more say in policy decisions than other active contributors to discussion on the libraries mailing list. We hope therefore that the membership of the committee does not need to be terribly formal. The only difficulty comes when consensus cannot be reached on an issue where making some decision is widely agreed to be better than making no decision. There is no specified protocol for this situation at this stage.
So I'm a bit confused about what the purpose of the steering committee's recommendation would be. Would it amount to a decision about inclusion, or an expression of their opinion in the hope of guiding the community towards a consensus, or something else? The first choice contradicts what Duncan said was the role of the committee, while the second doesn't seem any more worthwhile than individual members expressing their own opinions separately.
Yes, there's clearly some confusion. It's not the job of the steering committee to decide on individual packages going in. We want that to be a community review process. The steering committee can use this or some other package as a concrete example to help the community discuss what the criteria for package inclusion ought to be. Having a specific example may help to clarify the issue (or the details might distract). Duncan

On Thu, Aug 6, 2009 at 11:22 AM, Sittampalam,
Ganesh
Don Stewart wrote:
Here's a ticket for Simon Marlow's proposal:
http://trac.haskell.org/haskell-platform/ticket/86
Let's discuss, then have the steering committee recommend yay/nay.
In http://www.haskell.org/pipermail/libraries/2009-July/012139.html, Duncan said:
It is not the intention that the committee members get much more say in policy decisions than other active contributors to discussion on the libraries mailing list. We hope therefore that the membership of the committee does not need to be terribly formal. The only difficulty comes when consensus cannot be reached on an issue where making some decision is widely agreed to be better than making no decision. There is no specified protocol for this situation at this stage.
So I'm a bit confused about what the purpose of the steering committee's recommendation would be. Would it amount to a decision about inclusion, or an expression of their opinion in the hope of guiding the community towards a consensus, or something else? The first choice contradicts what Duncan said was the role of the committee, while the second doesn't seem any more worthwhile than individual members expressing their own opinions separately.
In my opinion the committee should just provide the framework in which the discussion takes place (i.e. a procedure for adding packages). It should also make sure that decisions get made and documented so they can be referred to in the future in case the same issues are raised again. I'm working on such a procedure and will proposed it to the community soon. Cheers, Johan
participants (15)
-
Alexander Dunlap
-
Christian Maeder
-
Denis Bueno
-
Don Stewart
-
Duncan Coutts
-
Felipe Lessa
-
Ian Lynagh
-
Jean-Philippe Bernardy
-
Johan Tibell
-
Krasimir Angelov
-
Malcolm Wallace
-
Neil Mitchell
-
Simon Marlow
-
Sittampalam, Ganesh
-
wren ng thornton