
Hello library people, I have noticed that many projects include a 'concatMapM' function: concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b] I think this is useful in general, so let's add it to Control.Monad. Trac ticket: http://hackage.haskell.org/trac/ghc/ticket/2042 Deadline for discussion: 2 weeks from now, January 28 Twan

Twan van Laarhoven wrote:
Hello library people,
I have noticed that many projects include a 'concatMapM' function:
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
I think this is useful in general, so let's add it to Control.Monad.
Me too. (therefore I think it should be added.) ~Isaac

isaacdupree:
Twan van Laarhoven wrote:
Hello library people,
I have noticed that many projects include a 'concatMapM' function:
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
I think this is useful in general, so let's add it to Control.Monad.
Me too. (therefore I think it should be added.)
(+1) seems reasonable.

Hello Twan, Monday, January 14, 2008, 7:41:08 PM, you wrote:
I have noticed that many projects include a 'concatMapM' function:
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
I think this is useful in general, so let's add it to Control.Monad.
the one thing that you miss - each time you add popular function to the base library, all programs that include this function becomes incompatible with next GHC version. i wonder whether anyone here has the experience of writing large programs and maintaining them through the years? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

bulat.ziganshin:
Hello Twan,
Monday, January 14, 2008, 7:41:08 PM, you wrote:
I have noticed that many projects include a 'concatMapM' function:
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
I think this is useful in general, so let's add it to Control.Monad.
the one thing that you miss - each time you add popular function to the base library, all programs that include this function becomes incompatible with next GHC version. i wonder whether anyone here has the experience of writing large programs and maintaining them through the years?
There has to be some path to migrate code into base. Do you have any examples of applications that will break, if this is added? -- Don

On Mon, 14 Jan 2008, Don Stewart wrote:
bulat.ziganshin:
Hello Twan,
Monday, January 14, 2008, 7:41:08 PM, you wrote:
I have noticed that many projects include a 'concatMapM' function:
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
I think this is useful in general, so let's add it to Control.Monad.
the one thing that you miss - each time you add popular function to the base library, all programs that include this function becomes incompatible with next GHC version. i wonder whether anyone here has the experience of writing large programs and maintaining them through the years?
I had to adapt programs for every new release of GHC. Quite annoying. These were caused by new standard instances or removed packages. However I usually import Control.Monad either by import Control.Monad (func) or import qualified Control.Monad as Monad Both variants are safe with respect to additions to Control.Monad. (This is also the reason why these two types of imports are the only ones in the Modula languages. - On the other hand they have built-in control structures and types, so they don't need a Prelude for that.)

the one thing that you miss - each time you add popular function to the base library, all programs that include this function becomes incompatible with next GHC version. i wonder whether anyone here has the experience of writing large programs and maintaining them through the years?
I import only the functions I need from libraries that I don't own myself to minimize that effect. That said, feature creep is definitely a problem. I think the GHC team will be the first to agree. But this particular function really is a natural. One point to consider - perhaps nowadays the type ought to be: concatMapM :: (Monad m, Traversable t) => (a -> m (t b)) -> t a -> m (t b) Regards, Yitz

Yitzchak Gale wrote:
One point to consider - perhaps nowadays the type ought to be:
concatMapM :: (Monad m, Traversable t) => (a -> m (t b)) -> t a -> m (t b)
I don't think that works in such generality since that would imply join :: Traversable t => t (t c) -> t c join = runIdentity . concatMapM return (set a = t c and b = c ). Regards, apfelmus

I wrote:
perhaps nowadays the type ought to be: concatMapM :: (Monad m, Traversable t) => (a -> m (t b)) -> t a -> m (t b)
apfelmus wrote:
I don't think that works in such generality since that would imply join :: Traversable t => t (t c) -> t c join = runIdentity . concatMapM return
Since return for the Identity monad is essential the identity, shouldn't we always have mapM return = return for that monad? In that case, your formula is indeed always true: runIdentity . concatMapM return = runIdentity . liftM join . mapM return = runIdentity . liftM join . return = runIdentity . return . join = join Regards, Yitz

Yitzchak Gale wrote:
perhaps nowadays the type ought to be: concatMapM :: (Monad m, Traversable t) => (a -> m (t b)) -> t a -> m (t b)
apfelmus wrote:
I don't think that works in such generality since that would imply join :: Traversable t => t (t c) -> t c join = runIdentity . concatMapM return
Since return for the Identity monad is essential the identity, shouldn't we always have
mapM return = return
for that monad?
Yes, since mapM f = sequence . map f for all monads and sequence = id :: [Identity a] -> Identity [a] for the identity monad.
In that case, your formula is indeed always true:
runIdentity . concatMapM return = runIdentity . liftM join . mapM return = runIdentity . liftM join . return = runIdentity . return . join = join
Indeed, assuming that concatMapM f = liftM join . mapM f of course. What I wanted to say is that given the existence of a function concatMapM of the aforementioned type, you can construct a function of the type Traversable t => t (t a) -> t a which basically means (modulo laws) that every Traversable would have to be a monad. Since this is not always the case (really?), such a concatMapM that works for all Traversable t does not exist. Regards, apfelmus

I wrote:
perhaps nowadays the type ought to be: concatMapM :: (Monad m, Traversable t) => (a -> m (t b)) -> t a -> m (t b)
apfelmus wrote:
I don't think that works in such generality since that would imply... that every Traversable would have to be a monad.
Ah, of course. Sorry, I wrote that in the wee hours of the morning. Now I also understand Ross Patterson's answer - that a Monoid structure could also be substituted for the Monad structure, because concat generalizes both to join and to mappend.
Since this is not always the case (really?)
Right. Given a tree of trees, there are many ways to paste them together into a single tree, but all of those ways use the actual tree structure, not just the fact that I can traverse over trees. You can't paste them together - but you can traverse them. So I guess the corresponding concept for traversables is that are composable over monads: mapMapM :: (Traversable t, Traversable t', Monad m) => (b -> m c) -> (a -> m (t b)) -> t' a -> m (t' (t c)) mapMapM f g = (>>= mapM (mapM f)) . mapM g I don't immediately see any composability over applicatives. Am I missing something obvious? Thanks, Yitz

On Mon, Jan 14, 2008 at 11:00:15PM +0200, Yitzchak Gale wrote:
One point to consider - perhaps nowadays the type ought to be:
concatMapM :: (Monad m, Traversable t) => (a -> m (t b)) -> t a -> m (t b)
Perhaps (using mapM from Data.Traversable): foldMapM :: (Monad m, Traversable f, Monoid v) => (a -> m v) -> f a -> m v foldMapM f = liftM fold . mapM f (with an Applicative conterpart too) But is this too small, and too orthogonal a combination, for the library?

Hi folks I think Ross has boiled it down pretty well... On 14 Jan 2008, at 22:53, Ross Paterson wrote:
Perhaps (using mapM from Data.Traversable):
foldMapM :: (Monad m, Traversable f, Monoid v) => (a -> m v) -> f a -> m v foldMapM f = liftM fold . mapM f
(with an Applicative conterpart too)
(As with many numerous episodes, I guess the need for monadic versions of applicative operations is something we have to live with for the moment. There is nothing essentially monadic going on here.) ...but you can go a little further. concatMapM, foldMapM, etc, are just newtype isotopes of foldMap. Here's what I'd do: it's perhaps not 98y enough (MPTCs, fundeps) for all but a far-flung corner of the library. What do you think? Step 1. Introduce a general utility to support the newtype-adds-structure pattern
class Unpack p u | p -> u where unpack :: p -> u
and when you create a newtype, instantiate Unpack. For example
newtype AMonoid a x = AMonoid {aMonoid :: a x}
instance Unpack (AMonoid a x) (a x) where unpack = aMonoid
I don't like having to remember a zillion unpacking functions. If you want to be more explicit, eg, to push types in, add
un :: Unpack p u => (u -> p) -> p -> u un _ = unpack
so (un AMonoid) is another name for aMonoid. Step 2. Implement this crunchy little third-order gadget.
ala :: Unpack p' u' => (u -> p) -> ((a -> p) -> a' -> p') -> (a -> u) -> a' -> u' ala pack hitWith hammer = unpack . hitWith (pack . hammer)
The idea is that (ala pack hitWith) invokes the map-like operator hitWith, but exploiting the extra structure identified by the packer, typically a newtype constructor. These two greatly increase the value of higher-order operations like traverse, and correspondingly reduce the need to extend one's library with special cases of them. Without the Unpack MPTC, you could at least add
modulo :: (u -> p) -> (p' -> u') -> ((a -> p) -> a' -> p') -> (a -> u) -> a' -> u' modulo fancy plain hitWith hammer = plain . hitWith (fancy . hammer)
which may be worth having a standard name for. Step 3. Expose the structure you need. Here, it's applicative lifting of monoids (you can add your own monadic version).
instance (Applicative a, Monoid x) => Monoid (AMonoid a x) where mempty = AMonoid (pure mempty) mappend (AMonoid x) (AMonoid y) = AMonoid (pure mappend <*> x <*> y)
This is a generally useful way to be specific about a very common kind of derived monoid structure. And now we're home!
parpSplat :: (Applicative parp, Foldable f, Monoid splat) => (x -> parp splat) -> f x -> parp splat parpSplat = ala AMonoid foldMap -- modulo AMonoid aMonoid foldMap
Haskell's classes are the best damn rhythm section in the industry: you hum it, they play it.
But is this too small, and too orthogonal a combination, for the library?
IMHO, yes. All the best Conor

On Tue, Jan 15, 2008 at 08:31:48PM +0000, Conor McBride wrote:
And now we're home!
parpSplat :: (Applicative parp, Foldable f, Monoid splat) => (x -> parp splat) -> f x -> parp splat parpSplat = ala AMonoid foldMap -- modulo AMonoid aMonoid foldMap
Unfolding these definitions, a shorter (but less scenic) route to this particular destination is: foldMapM :: (Monad m, Foldable t, Monoid v) => (a -> m v) -> t a -> m v foldMapM f = Data.Foldable.foldr mappend_f (return mempty) where mappend_f x y = liftM2 mappend (f x) y foldMapA :: (Applicative f, Foldable t, Monoid v) => (a -> f v) -> t a -> f v foldMapA f = Data.Foldable.foldr mappend_f (pure mempty) where mappend_f x y = mappend <$> f x <*> y

Hello Yitzchak, Tuesday, January 15, 2008, 12:00:15 AM, you wrote:
I import only the functions I need from libraries that I don't own myself to minimize that effect.
i think that the better way will be to put all these functions into extralibs bundled with ghc. this will allow me to control which concrete version of lib i import and therefore which set of functions i've used. i don't like idea of editing my module imports each time i use new functions
That said, feature creep is definitely a problem. I think the GHC team will be the first to agree. But this particular function really is a natural.
yes. `forever` function was also so natural that my program becomes incompatible with ghc 6.8. it's really annoying! -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, I wrote:
I import only the functions I need from libraries that I don't own myself to minimize that effect.
Bulat Ziganshin wrote:
i think that the better way will be to put all these functions into extralibs bundled with ghc. this will allow me to control which concrete version of lib i import and therefore which set of functions i've used.
Yes. But you still need to put the new functions in the right place in the module hierarchy. How do we do that? For each module included in the bootlibs, would you have also Path.To.Module.Extra? That would be annoying. And it wouldn't even solve the problem: if you use Extra even once, you would go back to the same situation. Or maybe this: have two parallel streams of package versions in Cabal, with one from each installed at any given time. If you compile with -package foo_extra_1.2, that replaces all of the modules in foo_bootlib or foo_extra_<any other version>. But now you always need to have all versions of every package installed on your system at any time -- no, *two versions* of all versions of every package. Yuck. There has to be some reasonable mechanism of adding new features to the libraries, even if we try very hard to be very disciplined and use it only rarely.
i don't like idea of editing my module imports each time i use new functions
It is a little more work. And there is the lint problem. But I find it's worth it. Sometimes I'm lazy and just do import Library.Module without an import list. I'm almost always sorry later on. Regards, Yitz

Hi
Yes. But you still need to put the new functions in the right place in the module hierarchy. How do we do that?
You create a package extras. You do import Control.Monad.Extras in your package, rather than import Control.Monad. The extra's package wraps up all the CPP magic required to keep track of the additions to the base libraries, so you end up using concatMapM from Control.Monad if it is in your libraries, you use one from extras if its not. Creating this package extras isn't a massive amount of work, and would completely solve this problem. Personally, I don't care enough to actually write such a package, but if it existed I might use it.
i don't like idea of editing my module imports each time i use new functions
It is a little more work. And there is the lint problem. But I find it's worth it.
Sometimes I'm lazy and just do import Library.Module without an import list. I'm almost always sorry later on.
I never list functions I'm importing by name. If I ever am sorry later on, its usually for a few fractions of a millisecond at compile time (the advantage of using Hugs ;) ). Typically it can be fixed typically by deleting code, while always makes me smile. Thanks Neil

On Tue, 15 Jan 2008, Neil Mitchell wrote:
Yes. But you still need to put the new functions in the right place in the module hierarchy. How do we do that?
You create a package extras. You do import Control.Monad.Extras in your package, rather than import Control.Monad. The extra's package wraps up all the CPP magic required to keep track of the additions to the base libraries, so you end up using concatMapM from Control.Monad if it is in your libraries, you use one from extras if its not.
I don't like fixing bad style (import anonymously and unqualified) by even more bad style (CPP). The problem can nicely be solved by letting GHC emit warnings if you don't import carefully, and allow lazy importing style in Haskell Prime only as language extension. :-)

On Tue, 15 Jan 2008, Yitzchak Gale wrote:
Hi Bulat,
I wrote:
I import only the functions I need from libraries that I don't own myself to minimize that effect.
Bulat Ziganshin wrote:
i think that the better way will be to put all these functions into extralibs bundled with ghc. this will allow me to control which concrete version of lib i import and therefore which set of functions i've used.
Yes. But you still need to put the new functions in the right place in the module hierarchy. How do we do that?
For each module included in the bootlibs, would you have also Path.To.Module.Extra? That would be annoying. And it wouldn't even solve the problem: if you use Extra even once, you would go back to the same situation.
I collected some points at http://www.haskell.org/haskellwiki/Import_modules_properly

Twan van Laarhoven wrote:
I have noticed that many projects include a 'concatMapM' function:
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
Trac ticket: http://hackage.haskell.org/trac/ghc/ticket/2042 Deadline for discussion: 2 weeks from now, January 28
Deadline <= now, so here is a summary of the discussion: 1. In favor: - Twan van Laarhoven - Isaac Dupree - Don Stewart - Neil Mitchell 2. Sidetracked with discussion of generalizations: - Yitzchak Gale - apfelmus - Ross Paterson 3. Opposed to any additions to the base library: - Bulat Ziganshin I think we should ignore the generalization to genericSuperDuperConcatMapMXYZ for now :). On the other hand, Bulat raises a valid point. Adding things to the base library might break some programs, although they will be easy enough to fix. But what do we do with Bulat's point in this specific case? I see two options: a. Don't add anything to the base libraries anymore, ever. b. Go ahead and add the function. Most users will see the change as they upgrade to ghc 6.10, which might break other minor things anyway. Twan

Hi
1. In favor: - Twan van Laarhoven - Isaac Dupree - Don Stewart - Neil Mitchell
3. Opposed to any additions to the base library: - Bulat Ziganshin
I don't think 4 people is quite enough to overrule one persons objections, so I'd suggest that anyone reading this thread who does want this to go in (as it stands, without generalisation) should shout up now. I'd guess another couple of me-too's is enough to have a consensus. To add one more me-too, Matthew Naylor (http://www-users.cs.york.ac.uk/~mfn/) says:
(+1) Me too.
Thanks Neil

On Tue, 2008-01-29 at 12:18 +0000, Neil Mitchell wrote:
Hi
1. In favor: - Twan van Laarhoven - Isaac Dupree - Don Stewart - Neil Mitchell
3. Opposed to any additions to the base library: - Bulat Ziganshin
Is concatMapM vs concat <$> mapM really such an improvement? Maybe the proposal should rather be to remove concatMap, for it is merely a 3-character shorter version of concat . map...
I don't think 4 people is quite enough to overrule one persons objections, so I'd suggest that anyone reading this thread who does want this to go in (as it stands, without generalisation) should shout up now. I'd guess another couple of me-too's is enough to have a consensus.
To add one more me-too, Matthew Naylor (http://www-users.cs.york.ac.uk/~mfn/) says:
(+1) Me too.
Thanks
Neil _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi
Maybe the proposal should rather be to remove concatMap, for it is merely a 3-character shorter version of concat . map...
Wrong, its a 5-character shorter version of (concat . map). It's those brackets that I appreciate the removal of.
Is concatMapM vs concat <$> mapM really such an improvement?
Yes. It's 7 characters shorter than that. With 7 characters I could wipe my entire hard drive, those characters matter!! :-) Thanks Neil

On Tue, 29 Jan 2008, Thomas Schilling wrote:
On Tue, 2008-01-29 at 12:18 +0000, Neil Mitchell wrote:
Hi
1. In favor: - Twan van Laarhoven - Isaac Dupree - Don Stewart - Neil Mitchell
3. Opposed to any additions to the base library: - Bulat Ziganshin
Is concatMapM vs concat <$> mapM really such an improvement? Maybe the proposal should rather be to remove concatMap, for it is merely a 3-character shorter version of concat . map...
"(concat . map f) xs" is 5 characters longer than "concatMap f xs" ! Alternatives concat $ map f xs concat (map f xs) What about zipWith concatMap vs. zipWith (\f -> concat . map f) So far I used concatMap a lot and thus I think it's addition was valuable.

On Tue, Jan 29, 2008 at 12:18:44PM +0000, Neil Mitchell wrote:
1. In favor: - Twan van Laarhoven - Isaac Dupree - Don Stewart - Neil Mitchell
3. Opposed to any additions to the base library: - Bulat Ziganshin
I don't think 4 people is quite enough to overrule one persons objections, so I'd suggest that anyone reading this thread who does want this to go in (as it stands, without generalisation) should shout up now. I'd guess another couple of me-too's is enough to have a consensus.
I don't have much of an opinion about the particular function being discussed, but I'm strongly against freezing the base library at this point. Thanks Ian

Hello Ian, Tuesday, January 29, 2008, 5:56:48 PM, you wrote:
I don't have much of an opinion about the particular function being discussed, but I'm strongly against freezing the base library at this point.
reasons? when it should be freezed? as an example look at ghc itself - it's full of #ifdefs and borrowed libraries. is that organization is recommended haskell programming style? from my POV, base is dead body. it was possible to continue to split it into fragments while keeping backward compatibility and it was that i mean when proposed to do it. but this was not implemented in 6.8 so, i propose to does one of two things, either 1) freeze base and make new libs by *copying* code from there 2) add to ghc ability to reexport functions from other libs and make sure that new ghc will be compatible with old libs and vice versa anyway, i'm against adding new functions to base - please use library system with its versioning ability for this. why you want to inflate the only ghc library that can't be upgraded? :( btw, are you ever tried to compile old ghc versions with new ones - i bet that it will have the same compilation problems as my program :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, On Tue, Jan 29, 2008 at 07:17:44PM +0300, Bulat Ziganshin wrote:
Tuesday, January 29, 2008, 5:56:48 PM, you wrote:
I don't have much of an opinion about the particular function being discussed, but I'm strongly against freezing the base library at this point.
reasons?
I don't want to get into a long discussion about this, because I don't think we're going change our viewpoints, but the reason is because I think that freezing it would cause more pain overall. I would like to see some significant changes to the base package, e.g. in how exceptions are implemented (to avoid the gigantic import cycle that the current implementation causes, and also because I think Simon's proposed replacement is nicer to use).
when it should be freezed?
I'm not sure it ever should, but it would have to be an awful lot smaller first in my opinion.
as an example look at ghc itself - it's full of #ifdefs and borrowed libraries. is that organization is recommended haskell programming style?
GHC tries to be buildable with just a plain GHC install, no extra or upgraded libraries, going back as many GHC versions as possible. That's because of the hassle of bootstrapping it again if you fall too far behind. I wouldn't recommend for other Haskell code to go to such lengths. Thanks Ian

ndmitchell:
Hi
1. In favor: - Twan van Laarhoven - Isaac Dupree - Don Stewart - Neil Mitchell
3. Opposed to any additions to the base library: - Bulat Ziganshin
I don't think 4 people is quite enough to overrule one persons objections, so I'd suggest that anyone reading this thread who does want this to go in (as it stands, without generalisation) should shout up now. I'd guess another couple of me-too's is enough to have a consensus.
The problem is that the one objector is just fundamentally opposed to the very process of adding stuff to the base library, for this case and all others. Given that the consensus is that we *will* continue to improve the base library, this objection isn't relevant -- it doesn't address the proposal under consideration. Which leaves us with 4 in favour, and a few generalists. -- Don

Hi
The problem is that the one objector is just fundamentally opposed to the very process of adding stuff to the base library, for this case and all others.
True - I guess it must be objections to code, not to process to actually be a problem.
Which leaves us with 4 in favour, and a few generalists.
5, Matt Naylor as well. I really can't believe that everyone doesn't want this, I define concatMapM in so many programs.... Thanks Neil

Hello Neil, Tuesday, January 29, 2008, 8:55:18 PM, you wrote:
5, Matt Naylor as well. I really can't believe that everyone doesn't want this, I define concatMapM in so many programs....
i'm against this exactly because i use (and define) it in my program. freearc was already broken with 6.8 due to introduction of 'forever' and i don't like it to broke with every new major ghc version (or even minor one as some purists prefer). i wonder whether noone here write software that may be compiled by people outside of haskell island? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

3. Opposed to any additions to the base library: - Bulat Ziganshin
Add me to this list. "base" is not a convenience library, it should contain fundamentally important stuff. Cf. java.lang, which "Provides classes that are fundamental to the design of the Java programming language" http://java.sun.com/javase/6/docs/api/java/lang/package-summary.html The emphasis (I think) is on *design* of the *language*. Best regards, Johannes Waldmann.

waldmann:
3. Opposed to any additions to the base library: - Bulat Ziganshin
Add me to this list.
"base" is not a convenience library, it should contain fundamentally important stuff.
I think the Prelude is our equivalent here. base itself is fundamental stuff, plus what we use a lot.
Cf. java.lang, which "Provides classes that are fundamental to the design of the Java programming language" http://java.sun.com/javase/6/docs/api/java/lang/package-summary.html
The emphasis (I think) is on *design* of the *language*.
If the proposal is that nothing new be added to base, that needs to be done separately. And a case made for why what we have at the moment is fundamental, excluding all else. Remember, this is not a discussion about whether things are to be added to base -- we did that a year ago, and the library process is the result. -- Don

On Tue, 29 Jan 2008, Johannes Waldmann wrote:
3. Opposed to any additions to the base library: - Bulat Ziganshin
Add me to this list.
"base" is not a convenience library, it should contain fundamentally important stuff.
Cf. java.lang, which "Provides classes that are fundamental to the design of the Java programming language" http://java.sun.com/javase/6/docs/api/java/lang/package-summary.html
The emphasis (I think) is on *design* of the *language*.
The question is - where to add it, if not to Data.List? We could setup new Data.List.Extras. But this would have the same problem like Data.List. Is the solution to move Data.List from 'base' to 'containers' or so, since the basic list functions are already in Prelude?

Hello Henning, Tuesday, January 29, 2008, 9:54:18 PM, you wrote:
The question is - where to add it, if not to Data.List? We could setup new Data.List.Extras. But this would have the same problem like Data.List. Is the solution to move Data.List from 'base' to 'containers' or so, since the basic list functions are already in Prelude?
the whole problem is that base is hard-wired with ghc and CAN'T BE UPGRADED. so i propose to add new package for all those new funcs and freeze base to solve problem of ghc versions incompatibility -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Henning,
Tuesday, January 29, 2008, 9:54:18 PM, you wrote:
The question is - where to add it, if not to Data.List? We could setup new Data.List.Extras. But this would have the same problem like Data.List. Is the solution to move Data.List from 'base' to 'containers' or so, since the basic list functions are already in Prelude?
the whole problem is that base is hard-wired with ghc and CAN'T BE UPGRADED. so i propose to add new package for all those new funcs and freeze base to solve problem of ghc versions incompatibility
Freezing base is a bad idea. - we'd end up with silly packages called things like 'listexts' with Data.List.Exts. - we have no way of evolving the design of the libraries, no way to make improvements. We're stuck with a design which is widely acknowledged to be lacking in various serious ways (e.g. no Unicode in the IO library). What we propose to do instead is to provide better support for backwards compatibility. I'm honestly not sure whether this will lead to more problems, or whether it will just work nicely, but it's pretty clear we have to try. Before responding, take a good read through http://hackage.haskell.org/trac/ghc/wiki/PackageCompatibility In particular, I think the most practical approach is 4.3, although this doesn't give complete backwards compatibility. If you have a better suggestion, let's hear it - but please nothing of the form "oh, it must be possible to just do X", think about all the ramifications of "just doing X" and add a proposal to the wiki page, or write a new page. In addition to this, we need to get packages using the Package Versioning Policy: http://haskell.org/haskellwiki/Package_versioning_policy For this we need support in Cabal and/or Hackage. By the time we release GHC 6.10, we want most packages in Hackage using accurate dependencies, so that the majority will continue to work with GHC 6.10. Something else we have to think about is upgrades. We're now commonly seeing multiple versions of packages installed, leading to problems when resolving dependencies ends up with two different versions of a given package, and type errors ensue. It's probably time to start a new wiki page for thinking about solutions to this. Cheers, Simon

Freezing base is a bad idea.
- we'd end up with silly packages called things like 'listexts' with Data.List.Exts.
- we have no way of evolving the design of the libraries, no way to make improvements. We're stuck with a design which is widely acknowledged to be lacking in various serious ways (e.g. no Unicode in the IO library).
I've been thinking about this lately. As you mentioned, we have functions that do I/O with Strings. These functions can be split up into two groups: * Those who do binary I/O but (ab)use String to store binary data (e.g. the socket API.) We might want to change their type to [Word8] or something similar. * Those who do text I/O. We might want to add an encoding parameter to those or add other, identical functions that takes the encoding as a parameter and use a default encoding for the functions that lack explicit encoding. e.g.
readFile :: FilePath -> IO String -- defaults to some encoding readFileWithEnc :: Encoding -> FilePath -> IO String -- explicit encoding, should have a better function name
data Encoding = Ascii | Utf8 | Utf16 -- no ALL CAPS pretty please!
decode :: Encoding -> [Word8] -> String -- you read something from a socket, now you want to decode it
How would such a change fit into the package compatibility proposal number 4.3? Isn't there also an interaction with the Haskell' spec here as well if it defines a few of those functions? -- Johan

Hello Johan, Thursday, January 31, 2008, 2:35:06 PM, you wrote:
* Those who do text I/O. We might want to add an encoding parameter to those or add other, identical functions that takes the encoding as a parameter and use a default encoding for the functions that lack explicit encoding. e.g.
readFile :: FilePath -> IO String -- defaults to some encoding readFileWithEnc :: Encoding -> FilePath -> IO String -- explicit encoding, should have a better function name
i can quickly tell why it's bad idea. it doubles amount of i/o functions just for this particular need. then you will notice that we also need functions which don't lock Handle or add some other processing and number of functions will double again and again i don't even say that for practical programming you will quickly find that passing encoding for particular file down all the functions that work with it is a nightmare the right way to deal with "modifiers" is to attach them to the Handle itself like this: f <- openFile "name" >>= withLocking >>= withEncoding utf8 and now look at http://haskell.org/haskellwiki/Library/Streams ;)
data Encoding = Ascii | Utf8 | Utf16 -- no ALL CAPS pretty please!
btw, it's another bad idea which means that set of encodings cannot be changed without changing library. it will be especially "great" if we will hard-code this into base, meaning that in order to get support for new encodings you should upgrade your ghc and any new encodings will become available for ghc users ONE YEAR AFTER actual implementation in FP language, the best way to provide encoding is to define it as pair of functions: data Encoding = Encoding { encode :: String -> String , decode :: String -> String } utf8 = Encoding encodeUtf8 decodeUtf8 -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Jan 31, 2008 2:13 PM, Bulat Ziganshin
Hello Johan,
Thursday, January 31, 2008, 2:35:06 PM, you wrote:
* Those who do text I/O. We might want to add an encoding parameter to those or add other, identical functions that takes the encoding as a parameter and use a default encoding for the functions that lack explicit encoding. e.g.
readFile :: FilePath -> IO String -- defaults to some encoding readFileWithEnc :: Encoding -> FilePath -> IO String -- explicit encoding, should have a better function name
i can quickly tell why it's bad idea. it doubles amount of i/o functions just for this particular need. then you will notice that we also need functions which don't lock Handle or add some other processing and number of functions will double again and again
i don't even say that for practical programming you will quickly find that passing encoding for particular file down all the functions that work with it is a nightmare
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8
and now look at http://haskell.org/haskellwiki/Library/Streams ;)
data Encoding = Ascii | Utf8 | Utf16 -- no ALL CAPS pretty please!
btw, it's another bad idea which means that set of encodings cannot be changed without changing library. it will be especially "great" if we will hard-code this into base, meaning that in order to get support for new encodings you should upgrade your ghc and any new encodings will become available for ghc users ONE YEAR AFTER actual implementation
in FP language, the best way to provide encoding is to define it as pair of functions:
data Encoding = Encoding { encode :: String -> String , decode :: String -> String }
utf8 = Encoding encodeUtf8 decodeUtf8
Just to be clear here. I don't care (for the purpose of this email) what these functions will look like. I just provided some random examples. I was asking how changes to existing functions would be handled. It's interesting to hear your ideas on the topic none the less. :) -- Johan

Bulat Ziganshin wrote: (very sound software engineering arguments - can someone with The Force please copy Bulat's mail to Haskell/Category/Style ...) I agree completely, and just add one remark here :
data Encoding = Encoding { encode :: String -> String , decode :: String -> String }
utf8 = Encoding encodeUtf8 decodeUtf8
this is in fact a method table (Java speak) or a dictionary (Haskell), and Encoding is the interface (class) - except that we can have local instances by passing around dictionaries explicitly. This is similar to passing a Comparator object to some sorting routine. Best regards, Johannes. PS: go read any honest OO book on the benefits of interface oriented design - they know this stuff - they got there the hard way (that is, via C++ :-)

On Jan 31, 2008 4:10 PM, Johannes Waldmann
Bulat Ziganshin wrote:
(very sound software engineering arguments - can someone with The Force please copy Bulat's mail to Haskell/Category/Style ...)
I agree completely, and just add one remark here :
data Encoding = Encoding { encode :: String -> String , decode :: String -> String }
utf8 = Encoding encodeUtf8 decodeUtf8
this is in fact a method table (Java speak) or a dictionary (Haskell), and Encoding is the interface (class) -
except that we can have local instances by passing around dictionaries explicitly.
This is similar to passing a Comparator object to some sorting routine.
Best regards, Johannes.
PS: go read any honest OO book on the benefits of interface oriented design - they know this stuff - they got there the hard way (that is, via C++ :-)
With this approach I would like some facility (e.g. table) to lookup common encodings as the encoding used for a particular datum is not know at compile time in many applications (e.g. it's read from a HTTP Content-Type header or similar.)
lookupEncoding :: String -> Maybe Encoding
-- Johan

Johan Tibell wrote:
With this approach I would like some facility (e.g. table) to lookup common encodings as the encoding used for a particular datum is not know at compile time in many applications (e.g. it's read from a HTTP Content-Type header or similar.)
lookupEncoding :: String -> Maybe Encoding
In fact, there is probably use for several such lookup functions: one for each naming scheme for encodings (and there are several of those, largely overlapping). This lookupEncoding function can be implemented after the fact -- perhaps in a library dedicated to dealing with MIME content -- and it may look something like: lookupEncoding "ISO-8859-1" = Just iso8859_1 lookupEncoding "ISO-8859-2" = Just iso8859_2 ... lookupEncoding _ = Nothing And voila! You've got yourself a way to look up text encodings by name. All this praise of Java makes me nervous, because as a programmer interface, Java is *wrong* about text encodings. Its standard library treats strings, mainly, as the right type for talking about text encodings; and they are not! It keeps one global name-to-encoding mapping, assigns each encoding a canonical "Java name", which is sometimes invented out of thin air. The compiler has no list of encodings that will be available, so it doesn't complain if you hard-code a misspelled encoding name into your program. This stuff is *really* *bad*; it's part of why using Java is a chore rather than a joy. Obviously, I'd like to see Haskell avoid that route. I'm not saying anyone proposed going in that direction; but I got the sense that we may be wandering dangerously close. This is no less fundamental than a question of whether we use language features, or fear them because we fear committment. As Simon mentioned, perhaps there are more things that need to happen to make the language features to make them more compatibility-friendly; but we should make a concerted effort to dive right in and use language features for their intended purpose rather than timidly hang around the outside fringes. -- Chris Smith

Hello Johan, Thursday, January 31, 2008, 6:19:40 PM, you wrote:
data Encoding = Encoding { encode :: String -> String , decode :: String -> String }
With this approach I would like some facility (e.g. table) to lookup common encodings as the encoding used for a particular datum is not know at compile time in many applications (e.g. it's read from a HTTP Content-Type header or similar.)
lookupEncoding :: String -> Maybe Encoding
you may have several libs installed each one providing its own set of encodings, moreover some libs (e.g. iconv-based) may provide this info only at run-time (i.e. in IO monad) so it have meaning to require from authors of encoding libs/modules to provide "dictionaries" of encodings implemented, and combine these dictionaries yourself: myLookup = do iconvEncodings <- IConv.lookupEncoding return (stdEncodings <+> iconvEncodings <+> OtherLib.lookupEncoding) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Jan 31, 2008 7:45 PM, Bulat Ziganshin
Hello Johan,
Thursday, January 31, 2008, 6:19:40 PM, you wrote:
data Encoding = Encoding { encode :: String -> String , decode :: String -> String }
With this approach I would like some facility (e.g. table) to lookup common encodings as the encoding used for a particular datum is not know at compile time in many applications (e.g. it's read from a HTTP Content-Type header or similar.)
lookupEncoding :: String -> Maybe Encoding
you may have several libs installed each one providing its own set of encodings, moreover some libs (e.g. iconv-based) may provide this info only at run-time (i.e. in IO monad)
so it have meaning to require from authors of encoding libs/modules to provide "dictionaries" of encodings implemented, and combine these dictionaries yourself:
myLookup = do iconvEncodings <- IConv.lookupEncoding return (stdEncodings <+> iconvEncodings <+> OtherLib.lookupEncoding)
Hi Bulat, Sure. I would also prefer to have a minimal number of encoding provided in a GHC library.

Hello Johannes, Thursday, January 31, 2008, 6:10:14 PM, you wrote:
PS: go read any honest OO book on the benefits of interface oriented design - they know this stuff - they got there the hard way (that is, via C++ :-)
OOP is well known as "stripped FP" paradigm :) when FP just pass all the functions and data required for specialization of generic algorithm, OOP provides interfaces, virtual functions, anonymous classes, delegates and lots of other interesting ways to hide the fact of lack of first-class functions :) look at http://haskell.org/haskellwiki/OOP_vs_type_classes -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2008-01-31, Bulat Ziganshin
in FP language, the best way to provide encoding is to define it as pair of functions:
data Encoding = Encoding { encode :: String -> String , decode :: String -> String }
Except these types are lies.
data Encoding = Encoding { encode :: String -> Maybe [Word8] , decode :: [Word8] -> Maybe String }
-- Aaron Denney -><-

Bulat Ziganshin
the right way to deal with [text encoding] "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8
This is nice! I think the Haskell Way of interpreting bytes as Latin-1 - while unfortunate in today's multi-everything environment - is something we just have to live with. Too much code expects this behavior, and too many tasks require just reading ASCII to be burdened with complications of locales and character sets. Attaching modifiers to handles appears to solve the problem of retaining 100% backwards compatibility, while opening for dealing with modern character sets. Somebody raised the question of reading a Content-type field, etc: would it be possible to "rewind" a handle after setting encoding? For Content-type fields, I suspect the header is usually limited to ASCII anyway, so adding decoding for subsequent text is probably sufficient. But how about a 'withDefaultEncoding' modifier that inspects the first two (or four?) bytes for a Unicode BOM, and either sets decoding accordingly and continues, or sets encoding according to locale *and* lets the user read the first bytes when reading from the handle. -k -- If I haven't seen further, it is by standing in the footprints of giants

I think the Haskell Way of interpreting bytes as Latin-1 - while unfortunate in today's multi-everything environment - is something we just have to live with. Too much code expects this behavior, and too many tasks require just reading ASCII to be burdened with complications of locales and character sets.
Why do we have to live with it? I understand why we ended up with the situation we have today. Most languages have/had the same problem. It's being fixed in other languages like Python. Not fixing it makes it a huge pain to deal with Strings from different sources (e.g. libraries) since you don't know if the content is Unicode code points (which String is defined as containing) or raw bytes because the programmer used the wrong type.
.... But how about a 'withDefaultEncoding' modifier that inspects the first two (or four?) bytes for a Unicode BOM, and either sets decoding accordingly and continues, or sets encoding according to locale *and* lets the user read the first bytes when reading from the handle.
The BOM mark is not always present and is not enough to decide which encoding was used. You could invent and encoding of Unicode that doesn't use one. Some recommended reading (for everyone): http://www.joelonsoftware.com/articles/Unicode.html -- Johan

Hello Johan, Friday, February 1, 2008, 11:56:09 AM, you wrote:
I think the Haskell Way of interpreting bytes as Latin-1 - while unfortunate in today's multi-everything environment - is something we just have to live with. Too much code expects this behavior, and too many tasks require just reading ASCII to be burdened with complications of locales and character sets.
Why do we have to live with it? I understand why we ended up with the situation we have today. Most languages have/had the same problem.
the problem is just over-complication of existing Handle implementation - it's about 2kloc of high-messed code. taking into account that it lacks a lot of other required features, it's quite meaningless to spend a lot of time fixing it for just one particular problem i've implemented 2 versions of Streams library which includes everything i know about i/o (i.e. no networking, overlapped i/o or iconv) and started to implement its 3rd version which includes bytestring i/o but then switched to more interesting project. Streams is still the most complete haskell i/o library and quite useful. its main drawback is lack of docs, especially for second version, but to some degree you can understand it just by analogy with System.IO interfaces -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

From: libraries-bounces@haskell.org [mailto:libraries-bounces@haskell.org] On Behalf Of Ketil Malde
Somebody raised the question of reading a Content-type field, etc: would it be possible to "rewind" a handle after setting encoding? For Content-type fields, I suspect the header is usually limited to ASCII anyway, so adding decoding for subsequent text is probably sufficient.
I think this is relevant: http://www.haskell.org/pipermail/haskell-cafe/2004-September/006801.html Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

Bayley, Alistair wrote:
From: libraries-bounces@haskell.org [mailto:libraries-bounces@haskell.org] On Behalf Of Ketil Malde
Somebody raised the question of reading a Content-type field, etc: would it be possible to "rewind" a handle after setting encoding? For Content-type fields, I suspect the header is usually limited to ASCII anyway, so adding decoding for subsequent text is probably sufficient.
I think this is relevant:
http://www.haskell.org/pipermail/haskell-cafe/2004-September/006801.html
We've talked a lot in the past about a stream-layering IO abstraction. I'd forgotten about Oleg's post, thanks. Here are some others. There's the prototype I worked on: http://www.haskell.org/~simonmar/io/System.IO.html There's Bulat's Stream library, which is pretty complete: http://haskell.org/haskellwiki/Library/Streams And Takano Akio's version, in which he divides the type classes into smaller pieces. This is closer to the direction I thought we should go: http://yogimo.sakura.ne.jp/ssc/ Right now though, I'm not sure all this is going in the right direction. Dealing with all those mutable buffers is quite a headache (for the library writer, not the user), and lazy bytestrings have shown us that there are simpler ways to get good I/O performance. What's more, as Duncan Coutts has pointed out to me on more than one occasion, it's much easier to layer streams when the streams are lazy lists. As much as I hate to say it, there's a lot to be said for lazy I/O in this respect. However, lazy I/O has other problems - deterministically catching errors, unpredictable resource usage, unpredictable interaction with other I/O, and so on. Is there a nice solution? Something else we might look at is Oleg's left folds: http://okmij.org/ftp/Haskell/#fold-stream http://www.haskell.org/pipermail/haskell/2003-September/012741.html Cheers, Simon

Simon Marlow wrote:
Bayley, Alistair wrote:
From: libraries-bounces@haskell.org [mailto:libraries-bounces@haskell.org] On Behalf Of Ketil Malde
Somebody raised the question of reading a Content-type field, etc: would it be possible to "rewind" a handle after setting encoding? For Content-type fields, I suspect the header is usually limited to ASCII anyway, so adding decoding for subsequent text is probably sufficient.
I think this is relevant:
http://www.haskell.org/pipermail/haskell-cafe/2004-September/006801.html
We've talked a lot in the past about a stream-layering IO abstraction. I'd forgotten about Oleg's post, thanks.
Here are some others. There's the prototype I worked on:
http://www.haskell.org/~simonmar/io/System.IO.html
There's Bulat's Stream library, which is pretty complete:
http://haskell.org/haskellwiki/Library/Streams
And Takano Akio's version, in which he divides the type classes into smaller pieces. This is closer to the direction I thought we should go:
I should also mention John Goerzen's HVIO library: http://hackage.haskell.org/packages/archive/MissingH/1.0.0/doc/html/System-I... Cheers, Simon

Hello Simon, Friday, February 1, 2008, 1:46:33 PM, you wrote:
We've talked a lot in the past about a stream-layering IO abstraction.
There's Bulat's Stream library, which is pretty complete:
http://haskell.org/haskellwiki/Library/Streams
And Takano Akio's version, in which he divides the type classes into smaller pieces. This is closer to the direction I thought we should go:
I should also mention John Goerzen's HVIO library:
http://hackage.haskell.org/packages/archive/MissingH/1.0.0/doc/html/System-I...
to clear up things, HVIO was a basis for Streams, and Streams was a basis for SSC -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Simon, Friday, February 1, 2008, 1:31:37 PM, you wrote:
Right now though, I'm not sure all this is going in the right direction. Dealing with all those mutable buffers is quite a headache (for the library writer, not the user), and lazy bytestrings have shown us that there are simpler ways to get good I/O performance. What's more, as Duncan Coutts has pointed out to me on more than one occasion, it's much easier to layer streams when the streams are lazy lists. As much as I hate to say it, there's a lot to be said for lazy I/O in this respect. However, lazy I/O has other problems - deterministically catching errors, unpredictable resource usage, unpredictable interaction with other I/O, and so on.
also add lack of multithreading/locking support and questionable interaction with C libs. i still think that the proper solution is to provide imperative i/o library as the basis and build lazy bytestring one on the top of it. most users will use high-level library unfortunately, BS and Streams libs were never integrated together -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Right now though, I'm not sure all this is going in the right direction. Dealing with all those mutable buffers is quite a headache (for the library writer, not the user), and lazy bytestrings have shown us that there are simpler ways to get good I/O performance. What's more, as Duncan Coutts has pointed out to me on more than one occasion, it's much easier to layer streams when the streams are lazy lists. As much as I hate to say it, there's a lot to be said for lazy I/O in this respect. However, lazy I/O has other problems - deterministically catching errors, unpredictable resource usage, unpredictable interaction with other I/O, and so on. Is there a nice solution? Something else we might look at is Oleg's left folds:
http://okmij.org/ftp/Haskell/#fold-stream http://www.haskell.org/pipermail/haskell/2003-September/012741.html
I initially used lazy I/O with lazy bytestrings in my web server but I'm changing that behvior to use left folds instead precisely because of the reasons you (and Oleg) mentioned. Unfortunately, that means I need a incremental Parsec for bytestrings (I think) so there's yet another library to write. Oh well. :) -- Johan

Johan Tibell wrote:
I initially used lazy I/O with lazy bytestrings in my web server but I'm changing that behvior to use left folds instead precisely because of the reasons you (and Oleg) mentioned. Unfortunately, that means I need a incremental Parsec for bytestrings (I think) so there's yet another library to write.
It wouldn't be hard to take bytestringparser and perform the same transformation on it as Adam Langley did with his IncrementalGet parser for strict-binary. I've been skipping it due to lack of time, but it's an obviously right thing to do.

On Feb 1, 2008 9:35 AM, Bryan O'Sullivan
It wouldn't be hard to take bytestringparser and perform the same transformation on it as Adam Langley did with his IncrementalGet parser for strict-binary. I've been skipping it due to lack of time, but it's an obviously right thing to do.
I think the hurdle here would be that you can't easily rollback the state. Normally, in a parser one can just take the current state and revert to that if a parsing path fails. However, in an incremental parser, of the style of IncrementalGet, rolling back the state would mean that the additional data which has been supplied to the parser, via continuations, will be lost and needs to be resupplied. That's a non-solution because the caller shouldn't need to know anything about the internals of the parser. I think one could get around this by having a couple of states, the latter being a list of all the additional ByteStrings that the parser has received. Then, after having prospectively failed a certain parse path, the failure must include the list of additional data, which can be merged into the new state for the next prospective path. This failure value must be internal and, at the top level, translated into a more user-friendly failure. Unless something special is done, this also means that the incremental parser couldn't walk over huge streams of data, because it would still be holding all the input in case it gets reverted. Of course, the top level cannot be reverted, so maybe it's worth special casing this. AGL -- Adam Langley agl@imperialviolet.org http://www.imperialviolet.org 650-283-9641

On Feb 1, 2008 5:06 PM, Adam Langley
I think one could get around this by having a couple of states, the latter being a list of all the additional ByteStrings that the parser has received. Then, after having prospectively failed a certain parse path, the failure must include the list of additional data, which can be merged into the new state for the next prospective path. This failure value must be internal and, at the top level, translated into a more user-friendly failure.
That was actually bit tougher than I thought, but I got something working: http://www.imperialviolet.org/Incremental.hs Half the bottom functions are still commented out because I got bored, but the plus operator works (I think). I managed a couple of simple tests that I threw at it. I'm pretty sure the cutContinuation is a terrible hack but, apart from having continuations in both directions, it was the best that I could come up with. However, I obvious don't understand Parsec because I made the try operator redundant, and I'm pretty sure that shouldn't have happened. AGL -- Adam Langley agl@imperialviolet.org http://www.imperialviolet.org 650-283-9641

On Feb 2, 2008 1:34 PM, Adam Langley
I'm pretty sure the cutContinuation is a terrible hack but, apart from having continuations in both directions, it was the best that I could come up with. However, I obvious don't understand Parsec because I made the try operator redundant, and I'm pretty sure that shouldn't have happened.
Well, I still think that it's a pretty big hack, but since I'd worked out how to do choice in an incremental parser I added it to binary-strict in darcs. http://darcs.imperialviolet.org/darcsweb.cgi?r=binary-strict;a=summary specifically: http://darcs.imperialviolet.org/darcsweb.cgi?r=binary-strict;a=headblob;f=/s... And since I had the choice operator, I added some other parsing stuff (many, <|> etc) to IncrementalGet and Get, than abstracted it out with a class http://darcs.imperialviolet.org/darcsweb.cgi?r=binary-strict;a=headblob;f=/s... Now you can write parsers which work in both strict and incremental modes. If you remove the monomorphism restriction, they can do both in the same module. As a test I'm writing an HTTP parser (one which handles all the RFC stuff that no one ever believes is valid - like newlines in lists) and it seems to be working pretty well. AGL -- Adam Langley agl@imperialviolet.org http://www.imperialviolet.org 650-283-9641

Adam Langley wrote:
On Feb 1, 2008 9:35 AM, Bryan O'Sullivan
wrote: It wouldn't be hard to take bytestringparser and perform the same transformation on it as Adam Langley did with his IncrementalGet parser for strict-binary. I've been skipping it due to lack of time, but it's an obviously right thing to do.
I think the hurdle here would be that you can't easily rollback the state. Normally, in a parser one can just take the current state and revert to that if a parsing path fails. However, in an incremental parser, of the style of IncrementalGet, rolling back the state would mean that the additional data which has been supplied to the parser, via continuations, will be lost and needs to be resupplied. That's a non-solution because the caller shouldn't need to know anything about the internals of the parser.
I think one could get around this by having a couple of states, the latter being a list of all the additional ByteStrings that the parser has received. Then, after having prospectively failed a certain parse path, the failure must include the list of additional data, which can be merged into the new state for the next prospective path. This failure value must be internal and, at the top level, translated into a more user-friendly failure.
Unless something special is done, this also means that the incremental parser couldn't walk over huge streams of data, because it would still be holding all the input in case it gets reverted. Of course, the top level cannot be reverted, so maybe it's worth special casing this.
Would 'Parallel Parsing Processes' help here? See http://www.haskell.org/haskellwiki/Research_papers/Functional_pearls For a version that is easy to understand and implement, see Chuan-kai Lin's Unimo paper available from the author's home page. Cheers Ben

Hello Ketil, Friday, February 1, 2008, 10:52:02 AM, you wrote:
f <- openFile "name" >>= withLocking >>= withEncoding utf8
Attaching modifiers to handles appears to solve the problem of retaining 100% backwards compatibility, while opening for dealing with modern character sets.
may be it's too draconian restriction but i proposed just to use new library in the new code. we can provide easy way to switch from Handles by providing emulation module System.Stream.IO which exports things with the old names - Handle, hGetContents... - but new implementation
Somebody raised the question of reading a Content-type field, etc: would it be possible to "rewind" a handle after setting encoding? For Content-type fields, I suspect the header is usually limited to ASCII anyway, so adding decoding for subsequent text is probably sufficient. But how about a 'withDefaultEncoding' modifier that inspects the first two (or four?) bytes for a Unicode BOM, and either sets decoding accordingly and continues, or sets encoding according to locale *and* lets the user read the first bytes when reading from the handle.
core of my library is *interfaces*, not implementations. openFile provides a getByte/putByte interfaces and also trivial getChar/putChar which just reads/writes one byte. withEncoding modifier provides another getChar/putChar implementations what process several bytes at once. you can dress file to one or another modifier at any moment, its internal read/write pointer isn't affected: f <- openFile "name" content <- readLine f -- read first line using Latin-1 f' <- withEncoding (lookup content) f str <- readLine f' -- read second line using encoding given on first line -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin
may be it's too draconian restriction but i proposed just to use new library in the new code.
For backwards compatibility, I agree it would be preferable to retain the current default implementation, but opinions appear to differ. Whatever.
f <- openFile "name" content <- readLine f -- read first line using Latin-1 f' <- withEncoding (lookup content) f str <- readLine f' -- read second line using encoding given on first line
This is clear enough, but for the BOM-dependent decoding, you may have to do the equivalent of having the next call to 'readLine' re-read the first line instead. -k -- If I haven't seen further, it is by standing in the footprints of giants

Hello Ketil, Friday, February 1, 2008, 4:29:02 PM, you wrote:
may be it's too draconian restriction but i proposed just to use new library in the new code.
For backwards compatibility, I agree it would be preferable to retain the current default implementation, but opinions appear to differ. Whatever.
the problem is not abstract "backward compatibility" but programs that switches from the old lib to the new one. they should get exactly the old services for old names - in order to not rewrite program new programs what need new behavior just need to import new interface which may provide UTF-8 encoding for text files by default
f <- openFile "name" content <- readLine f -- read first line using Latin-1 f' <- withEncoding (lookup content) f str <- readLine f' -- read second line using encoding given on first line
This is clear enough, but for the BOM-dependent decoding, you may have to do the equivalent of having the next call to 'readLine' re-read the first line instead.
it's not a problem - file pointer is retained in f and f' just interprets the bytes it read: f <- openFile "name" bom <- readBytes 4 f -- read first 4 bytes vRewind f f' <- withEncoding (lookup bom) f str <- readLine f' -- read first line using BOM encoding -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Feb 1, 2008 3:36 PM, Bulat Ziganshin
Hello Ketil,
Friday, February 1, 2008, 4:29:02 PM, you wrote:
may be it's too draconian restriction but i proposed just to use new library in the new code.
For backwards compatibility, I agree it would be preferable to retain the current default implementation, but opinions appear to differ. Whatever.
the problem is not abstract "backward compatibility" but programs that switches from the old lib to the new one. they should get exactly the old services for old names - in order to not rewrite program
Couldn't we handle backward compability by having say a 1.x line and a 2.x line of a library and push fixes to both? I'm afraid that libraries will turn into a mess eventually if they must support all old software in new versions. -- Johan

Ketil Malde wrote:
But how about a 'withDefaultEncoding' modifier that inspects the first two (or four?) bytes for a Unicode BOM, and either sets decoding accordingly and continues, or sets encoding according to locale *and* lets the user read the first bytes when reading from the handle.
I really don't like the idea of gluing notions of encoding and decoding to Handles, because Handles are so limited in their usefulness. Even something as simple as reading an encrypted file defeats this approach. Never mind stream sockets, datagram sockets, memory mapped files, or any of a dozen other ways of getting data that will have an encoding.

Bulat Ziganshin wrote:
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8
IMO, global state is never "the right way" if it can be avoided. It will always lead to problems. Especially in a functional language like Haskell. Roman

On 2008-02-01, Roman Leshchinskiy
Bulat Ziganshin wrote:
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8
IMO, global state is never "the right way" if it can be avoided. It will always lead to problems. Especially in a functional language like Haskell.
This isn't global state, but local to the handle, and only affects where the handle is passed in. It's just extending an opaque data type. -- Aaron Denney -><-

Aaron Denney wrote:
On 2008-02-01, Roman Leshchinskiy
wrote: Bulat Ziganshin wrote:
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8 IMO, global state is never "the right way" if it can be avoided. It will always lead to problems. Especially in a functional language like Haskell.
This isn't global state, but local to the handle, and only affects where the handle is passed in. It's just extending an opaque data type.
If I can destructively change the encoding assocated with a Handle, then it's global state. Roman

On 2008-02-01, Roman Leshchinskiy
Aaron Denney wrote:
On 2008-02-01, Roman Leshchinskiy
wrote: Bulat Ziganshin wrote:
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8 IMO, global state is never "the right way" if it can be avoided. It will always lead to problems. Especially in a functional language like Haskell.
This isn't global state, but local to the handle, and only affects where the handle is passed in. It's just extending an opaque data type.
If I can destructively change the encoding assocated with a Handle, then it's global state.
Right. But the example given doesn't necessarily have that. x <- [5, 6] >>= (return .) (+ 1) No modification is going on, but return of new values. I don't know how Bulat's stream library is implemented, but I expected a new handle wrapping the old to be returned. -- Aaron Denney -><-

Aaron Denney wrote:
On 2008-02-01, Roman Leshchinskiy
wrote: Aaron Denney wrote:
Bulat Ziganshin wrote:
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8 IMO, global state is never "the right way" if it can be avoided. It will always lead to problems. Especially in a functional language like Haskell. This isn't global state, but local to the handle, and only affects where
On 2008-02-01, Roman Leshchinskiy
wrote: the handle is passed in. It's just extending an opaque data type. If I can destructively change the encoding assocated with a Handle, then it's global state. Right. But the example given doesn't necessarily have that.
x <- [5, 6] >>= (return .) (+ 1)
No modification is going on, but return of new values.
True, but that is a very obfuscated way of doing this. If the handle is not modified destructively, then there is no need for withLocking etc. to be monadic. Roman

I was initially building strictify on top of System.Process.runInteractiveCommand. However, I soon ran into a fairly significant issue with the interface. Even once the process I was calling had terminated, and I had explicitly closed all its buffers, a zombie sh process was left around from it. As I was spawning, sequentially, lots of processes, this soon consumed too many resources and errored out. As I understand it, the sh process is used for redirection (in fact, I ended up implementing a variant of the same thing on top of System.Posix.Process eventually) and needs to stick around for a while, so that issues with lazyIO don't prevent the handles provided by command from terminating before we've read everything we want to. However, at the same time, it seems like a terrible idea to have these buffers stick around *forever*. I dug into the haskell code, but didn't look at the foreign C calls it was based on. This behavior seems pretty clearly broken to me, but I'm not sure what the exact solution should be. Possibly providing an explicit API method to shut the process down? Possibly blocking on polling its buffers and terminating the sh instance once all three buffers are explicitly or implicitly closed? --Sterl.

Sterling Clover wrote:
Even once the process I was calling had terminated, and I had explicitly closed all its buffers, a zombie sh process was left around from it.
Make sure to call waitForProcess on each process handle when you are finished with it. Regards, Yitz

gale:
Sterling Clover wrote:
Even once the process I was calling had terminated, and I had explicitly closed all its buffers, a zombie sh process was left around from it.
Make sure to call waitForProcess on each process handle when you are finished with it.
Or even consider using say, newpopen, which wraps this up for you, http://www.cse.unsw.edu.au/~dons/code/newpopen/

Hmm... I thought I had been doing everything right, but now trying to reproduce this issue, I find I can't. It must have been the waitForProcess issue. Thanks for the advice, and sorry to trouble the list with this. --Sterl On Feb 4, 2008, at 1:34 PM, Don Stewart wrote:
gale:
Sterling Clover wrote:
Even once the process I was calling had terminated, and I had explicitly closed all its buffers, a zombie sh process was left around from it.
Make sure to call waitForProcess on each process handle when you are finished with it.
Or even consider using say, newpopen, which wraps this up for you,

Hello Roman, Monday, February 4, 2008, 4:18:43 AM, you wrote:
True, but that is a very obfuscated way of doing this. If the handle is not modified destructively, then there is no need for withLocking etc. to be monadic.
withLocking = fmap WithLocking newMVar -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Roman, Friday, February 1, 2008, 11:03:36 AM, you wrote:
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8
IMO, global state is never "the right way" if it can be avoided. It will always lead to problems. Especially in a functional language like Haskell.
so you propose something like this: s <- readString "/path/filename" TextMode "utf8" line_num ? :) please read http://haskell.org/haskellwiki/Library/Streams - it's not what you have imagined reading this example -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Roman,
Friday, February 1, 2008, 11:03:36 AM, you wrote:
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8
IMO, global state is never "the right way" if it can be avoided. It will always lead to problems. Especially in a functional language like Haskell.
so you propose something like this:
s <- readString "/path/filename" TextMode "utf8" line_num
No. In my view, file handles and encodings exist on completely different levels of abstraction. The former are (or ought to be) simply an interface to the underlying OS capabilities. The latter would be part of a high-level I/O library which shouldn't even have the concept of a handle (and should use typed I/O). Also, it doesn't always make sense to associate an encoding with an entire file. For instance, a Russian-Greek dictionary might use ISO 8859-5 for Russian words and ISO 8859-7 for Greek ones. Roman

On Sat, 2 Feb 2008, Roman Leshchinskiy wrote:
Bulat Ziganshin wrote:
Hello Roman,
Friday, February 1, 2008, 11:03:36 AM, you wrote:
the right way to deal with "modifiers" is to attach them to the Handle itself like this:
f <- openFile "name" >>= withLocking >>= withEncoding utf8
IMO, global state is never "the right way" if it can be avoided. It will always lead to problems. Especially in a functional language like Haskell.
so you propose something like this:
s <- readString "/path/filename" TextMode "utf8" line_num
No. In my view, file handles and encodings exist on completely different levels of abstraction.
What about changing the subject in order to preserve the thread for further contributions to the concatMapM issue?

Hello Simon, Thursday, January 31, 2008, 2:15:58 PM, you wrote:
Freezing base is a bad idea.
- we'd end up with silly packages called things like 'listexts' with Data.List.Exts.
- we have no way of evolving the design of the libraries, no way to make improvements. We're stuck with a design which is widely acknowledged to be lacking in various serious ways (e.g. no Unicode in the IO library).
"Freezing base is a bad idea" only in the situation when we fear to duplicate any code. but really this leads to situation when the same code needs to be duplicated in every serious program, starting from GHC itself! why i have Utils module with dozens of list funcs? why you duplicated in GHC bag, bitset, encoding support, finite maps and lots of other standard code? i propose to freeze base in its current state and duplicate everything we want to evolve to separate libs. want to evolve i/o libs? no problem - just copy system.io to new.system.io and add anything you want. this new implementation will be outside of base so everyone will be able to use just the version he need at last end, "old good things" in base will remain only for backward compatibility with "old good books" like haskell98 package now used and as a base for other libraries, like GHC.* modules now used we shouldn't take new code into the base library because this only makes problem harder. are you not consider as a problem that it's impossible to develop code which will work with different ghc versions? in particular, i think we *have* library which supports unicode. it's not mature enough but it's better to evolve this lib or write another one which will be independent of base instead of making any changes to existing 2kloc Handle implementation
What we propose to do instead is to provide better support for backwards compatibility. I'm honestly not sure whether this will lead to more problems, or whether it will just work nicely, but it's pretty clear we have to try.
Before responding, take a good read through
http://hackage.haskell.org/trac/ghc/wiki/PackageCompatibility
first, now it is clear how to handle situation in 6.8 - with 4.2 we will have no more problems than with previous ghc upgrades
"Each time we split base we have to invent a new name for it, and we accumulate a new compatibility wrapper for the old one."
not true. for previous base versions, we never declared that it obeys HLP (haskell libraries policy), so users was absolutely right using general "base" dependency. for newbase library we will need to declare this and require that user specify "newbase 1.*" dependency, so newbase 2.0+ can make any API changes my proposal of freezing the base is exactly what i propose to do in order to finally solve "base problem". the proposed solution seems unusual for the first look but it really works and really solves the problem for 100%. actually, it's much better than duplicating code in every application program. the main disadvantage of duplicated code - maintenance costs - will be probably zero in this case because existing code in base rarely need to be fixed
For this we need support in Cabal and/or Hackage. By the time we release GHC 6.10, we want most packages in Hackage using accurate dependencies, so that the majority will continue to work with GHC 6.10.
a few days ago i've released first version of my GUI program. it had support for 69 localizations. how it was done? i just wrote script which translated language files of another program with close functionality :) we have only two ways to make all hackage libs compatible with 6.10 - either make *ghc* compatible with existing libs or *convert* these libs to the new format. but forcing authors to upgrade their libs is a bad idea. now i have feeling that goals of ghc/cabal/hackage developers isn't to provide eternal compatibility but to research various ways of providing such compatibility and write interesting papers about user reaction to all their experiments. sorry, but it is what i see
Something else we have to think about is upgrades. We're now commonly seeing multiple versions of packages installed, leading to problems when resolving dependencies ends up with two different versions of a given package, and type errors ensue. It's probably time to start a new wiki page for thinking about solutions to this.
sure. one idea we can import from my proposal is to recommend users to write their code against some "gem" of libraries - HSL-2008, HSL-2009... -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Feb 5, 2008 10:00 PM, Bulat Ziganshin
i propose to freeze base in its current state and duplicate everything we want to evolve to separate libs. want to evolve i/o libs? no problem - just copy system.io to new.system.io and add anything you want. this new implementation will be outside of base so everyone will be able to use just the version he need
Please do not use the package or library name for versioning or we'll end up with New.New.New.System.IO or Newer.Than.The.Third.Old.System.IO.That.Johan.Wrote ;). There will always be a new versions. Use the package's version number for versioning. -- Johan

Neil Mitchell wrote:
Orthogonality.
Indeed. If a proposed function's name is "fooBar", because it intends to be a combination of foo and bar, then "foo . bar" is already a perfect name. I think you'd recognize a useful abstraction by the fact that it has an obvious "stand-alone" name. Otherwise, it's not really an abstraction, is it? Best regards, Johannes Walmann.

Hi On 29 Jan 2008, at 12:29, Neil Mitchell wrote:
Hi
I think we should ignore the generalization to genericSuperDuperConcatMapMXYZ for now :).
Why?
Orthogonality.
What's orthogonal to what, here? I'm trying to understand why the generalization is irrelevant (or merely unwelcome) to the discussion of whether or not the special case should be added to the library.
It is silly to have have superConcatMapM, but not superMapM. If that wants doing it should be a separate proposal after this one.
If you peer at it closely, you'll notice that traverse is kind of like a generalized mapM. If you peer at it closely, you'll notice that concatMapM, apart from being unnecessarily specific to lists and unnecessarily specific to monads, is a newtype isotope of foldMap. Is it worth thinking a bit more about how to exploit the functionality that's already in the library? All the best Conor

On Tue, 2008-01-29 at 12:53 +0000, Conor McBride wrote:
What's orthogonal to what, here? I'm trying to understand why the generalization is irrelevant (or merely unwelcome) to the discussion of whether or not the special case should be added to the library.
I think the point is that it'd be a bit inconsistent if the only function in Control.Monad that was generalised to arbitrary Traversable, Monoid etc was concatMapM. The point continues that if we do indeed want to generalise all the functions in Data.List and/or Control.Monad then that should be a separate proposal. Duncan

Hi Duncan On 30 Jan 2008, at 10:53, Duncan Coutts wrote:
On Tue, 2008-01-29 at 12:53 +0000, Conor McBride wrote:
What's orthogonal to what, here? I'm trying to understand why the generalization is irrelevant (or merely unwelcome) to the discussion of whether or not the special case should be added to the library.
I think the point is that it'd be a bit inconsistent if the only function in Control.Monad that was generalised to arbitrary Traversable, Monoid etc was concatMapM.
This may be a reasonable distinction between concerns, but they're hardly orthogonal. The question of whether or not such generalizations are likely or desirable, sooner or later, is clearly relevant to the issue of how lame a duck concatMapM is likely to be, hence whether or not it should be added.
The point continues that if we do indeed want to generalise all the functions in Data.List and/or Control.Monad then that should be a separate proposal.
An interesting question is the extent to which this has already happened. My issue with concatMapM has, all along, been that it is a special case of foldMap, given the appropriate instance of Data.Monoid. We don't have to contemplate adding a new super duper general thrudsplingblatter to the library, giving it a silly name the better to travesty the mere suggestion, because foldMap is already in the library: it's a question of learning to make more and better use of it. I guess I'm advocating a general policy of "more structures; fewer functions", exploiting the power of instance inference to deliver the usual structure-respecting whatever, rather than giving all the instances individual names. Less is more. Or maybe I'm just a grumpy old math-troll trying to hassle people away from getting on in the obvious manner with some obviously desirable functionality. You choose Conor

On Tue, 29 Jan 2008, Twan van Laarhoven wrote:
Twan van Laarhoven wrote:
I have noticed that many projects include a 'concatMapM' function:
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
Trac ticket: http://hackage.haskell.org/trac/ghc/ticket/2042 Deadline for discussion: 2 weeks from now, January 28
Deadline <= now, so here is a summary of the discussion:
1. In favor: - Twan van Laarhoven - Isaac Dupree - Don Stewart - Neil Mitchell
2. Sidetracked with discussion of generalizations: - Yitzchak Gale - apfelmus - Ross Paterson
3. Opposed to any additions to the base library: - Bulat Ziganshin
I think we should ignore the generalization to genericSuperDuperConcatMapMXYZ for now :). On the other hand, Bulat raises a valid point.
In consider Bulat's point as preservation of unfavorable coding style (namely unqualified anonymous import). This method does not scale well and you can motivate stop of any development this way. So I object to Bulat's argument, but not necessarily vote particularly for concatMapM, since I didn't need it so far - which can also mean, that I have always worked-around it without noticing it. I think a generalization to Traversal would be nice. This would make these classes certainly more useful.
Adding things to the base library might break some programs, although they will be easy enough to fix. But what do we do with Bulat's point in this specific case? I see two options:
a. Don't add anything to the base libraries anymore, ever.
The current state is: Prelude's list functions are imported automatically and unqualified and thus should not be extended. However Data.List functions must be imported explicitely and then should be imported qualified or by name. This does not only avoid name clashes but also simplifies reading programs. http://www.haskell.org/haskellwiki/Import_modules_properly
b. Go ahead and add the function. Most users will see the change as they upgrade to ghc 6.10, which might break other minor things anyway.
This would be a good opportunity to switch to a more friendly importing style.

Hello Henning, Tuesday, January 29, 2008, 6:35:28 PM, you wrote:
In consider Bulat's point as preservation of unfavorable coding style (namely unqualified anonymous import). This method does not scale well and you can motivate stop of any development this way. So I object to Bulat's argument, but not necessarily vote particularly for concatMapM, since I didn't need it so far - which can also mean, that I have always worked-around it without noticing it.
so you will prefer to add it immediately to 6.8.*? i wonder how much code you write and which tool you use. my tools can't automatically insert these imports and i don't have time to do this monkey work by hand - and anyway i consider as bad programming style trying to replace package manager with home-grown tricks. the actual problem is hard-wired base package -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Tue, 29 Jan 2008, Bulat Ziganshin wrote:
Hello Henning,
Tuesday, January 29, 2008, 6:35:28 PM, you wrote:
In consider Bulat's point as preservation of unfavorable coding style (namely unqualified anonymous import). This method does not scale well and you can motivate stop of any development this way. So I object to Bulat's argument, but not necessarily vote particularly for concatMapM, since I didn't need it so far - which can also mean, that I have always worked-around it without noticing it.
so you will prefer to add it immediately to 6.8.*?
Why a GHC version? I thought that we speak about the 'base' package.
i wonder how much code you write
enough each day
and which tool you use.
NEdit. I use almost only qualified imports and named imports and have my modules designed to be used in this way, write signatures for all top-level variables and use -Wall.
my tools can't automatically insert these imports and i don't have time to do this monkey work by hand - and anyway i consider as bad programming style trying to replace package manager with home-grown tricks.
What tricks?

Hello Twan, Tuesday, January 29, 2008, 3:11:45 PM, you wrote:
I think we should ignore the generalization to genericSuperDuperConcatMapMXYZ for now :). On the other hand, Bulat raises a valid point. Adding things to the base library might break some programs, although they will be easy enough to fix. But what do we do with Bulat's point in this specific case? I see two options:
i have several hundred one-liners in my Utils.hs. with such speed of adding these funcs to the base, you will add only these funcs the next 10 years. does this mean that haskell hackers will continue to mutate the language these next 10 years? :( i appeal to Haskell authorities - please agree with me in recognizing importance of language stability and take this decision. just a list of problems due to mutations in base library i've senn on the list in this few weeks: 1) hackage libs are compatible with only one version of ghc. in particular, when new version of ghc arrives, hackage is useless for it and this delays its adoption. some times later, this becomes pain for users of old ghc version. this also means that noone can just release his code as a library - he need to update it every year. moreover, this makes initiatives like cabal-install rather strange thing - that is advantage of automatic downloading/compilation if sometimes we need to edit cabal files? 2) unix ports are usually don't update to next ghc versions for a long time because this "breaks compilation of many things" 3) even shootout tests were not updated to 6.8 because it breaks compilation of these tests! 4) every week we see complaints from users who can't compile code written for previous ghc versions overall, i think that its hackers thinking - "required changes are trivial, so everyone can do it". there are many agents (non-haskellers, even non-programmers, automation tools) that can't do even trivial changes in haskell code/configs. and even for a experienced haskeller who was bothered to find info about required changes, this may be a good amount of work (when we change lot of modules/libs) and they have (like me) more restrictive requirements when we need to offer compatibility with many ghc versions so this is a headache without any real advantage. i propose to make new lib, supply it with the ghc, and include all new functionality here. at least this lib may be properly-versioned or not used at all -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2008-01-29, Bulat Ziganshin
Hello Twan,
Tuesday, January 29, 2008, 3:11:45 PM, you wrote:
I think we should ignore the generalization to genericSuperDuperConcatMapMXYZ for now :). On the other hand, Bulat raises a valid point. Adding things to the base library might break some programs, although they will be easy enough to fix. But what do we do with Bulat's point in this specific case? I see two options:
i have several hundred one-liners in my Utils.hs. with such speed of adding these funcs to the base, you will add only these funcs the next 10 years. does this mean that haskell hackers will continue to mutate the language these next 10 years? :(
That's the whole point of "avoiding success" -- so we can continue to make changes. -- Aaron Denney -><-

Hello Aaron, Tuesday, January 29, 2008, 10:23:46 PM, you wrote:
i have several hundred one-liners in my Utils.hs. with such speed of adding these funcs to the base, you will add only these funcs the next 10 years. does this mean that haskell hackers will continue to mutate the language these next 10 years? :(
That's the whole point of "avoiding success" -- so we can continue to make changes.
well, you want haskell that remains hacker's tool, i want haskell used for development of real programs, such as darcs and ghc itself -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2008-01-29, Bulat Ziganshin
Hello Aaron,
Tuesday, January 29, 2008, 10:23:46 PM, you wrote:
i have several hundred one-liners in my Utils.hs. with such speed of adding these funcs to the base, you will add only these funcs the next 10 years. does this mean that haskell hackers will continue to mutate the language these next 10 years? :(
That's the whole point of "avoiding success" -- so we can continue to make changes.
well, you want haskell that remains hacker's tool, i want haskell used for development of real programs, such as darcs and ghc itself
"Researchers' tool", rather. Hackers write programs that import entire modules willy-nilly. Real program can afford to import selectively or qualified for future proofing. A thought: perhaps Haskell prime should have local definitions shadow imported ones, rather than conflicting. Mandating a warning might be worth it though. -- Aaron Denney -><-

Hello Aaron, Tuesday, January 29, 2008, 11:40:23 PM, you wrote:
well, you want haskell that remains hacker's tool, i want haskell used for development of real programs, such as darcs and ghc itself
"Researchers' tool", rather. Hackers write programs that import entire modules willy-nilly. Real program can afford to import selectively or qualified for future proofing.
yes, "real programs" can even afford to be coded in C. i use haskell to speed up development, though -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Tue, Jan 29, 2008 at 01:11:45PM +0100, Twan van Laarhoven wrote:
I think we should ignore the generalization to genericSuperDuperConcatMapMXYZ for now :).
Why? I think the fact that this is a special case argues against inclusion in the core libraries. Also that it's a simple compound of existing functions. It seems there's a philosophical difference here, which has come up before (in the intercalate and &&& discussions, and probably others). Some feel that the purpose of the library is to make programs shorter, so it should have names for every common idiom and special case. On the other hand there's the view that the core libraries should be a smallish collection of general primitives with little overlap, so that programmers can become familiar with a powerful but manageable toolkit. Jon Fairbairn expanded on this viewpoint in a previous discussion. In this view, concatMap itself was a mistake, which must be retained for backward compatibility, but should not be used as a model for the future. If we are interested in accomodating both views, perhaps separate packages are the way to go.
participants (25)
-
Aaron Denney
-
Adam Langley
-
apfelmus
-
Bayley, Alistair
-
Ben Franksen
-
Bryan O'Sullivan
-
Bulat Ziganshin
-
Chris Smith
-
Conor McBride
-
Don Stewart
-
Duncan Coutts
-
Henning Thielemann
-
Ian Lynagh
-
Isaac Dupree
-
Johan Tibell
-
Johannes Waldmann
-
Ketil Malde
-
Neil Mitchell
-
Roman Leshchinskiy
-
Ross Paterson
-
Simon Marlow
-
Sterling Clover
-
Thomas Schilling
-
Twan van Laarhoven
-
Yitzchak Gale