Deprecating haskell98 module aliases

See http://hackage.haskell.org/trac/hackage/ticket/640 It seems to me that a warning on using the 'haskell98' package wouldn't be a bad thing; those modules have since been split apart in better modules, the names are ever more unfamiliar, etc. But Duncan thinks it merits discussion. -- gwern

Gwern Branwen wrote:
See http://hackage.haskell.org/trac/hackage/ticket/640
It seems to me that a warning on using the 'haskell98' package wouldn't be a bad thing; those modules have since been split apart in better modules, the names are ever more unfamiliar, etc.
But Duncan thinks it merits discussion.
I'm all for the warnings. And regarding guest's comments, doesn't the Haskell 2010 standard[1] count as an "actual language standard"? If not, then what is it and why isn't it one? [1] http://www.haskell.org/pipermail/haskell/2009-November/021750.html -- Live well, ~wren

On Mon, Mar 8, 2010 at 3:36 PM, wren ng thornton
Gwern Branwen wrote:
See http://hackage.haskell.org/trac/hackage/ticket/640
It seems to me that a warning on using the 'haskell98' package wouldn't be a bad thing; those modules have since been split apart in better modules, the names are ever more unfamiliar, etc.
But Duncan thinks it merits discussion.
I'm all for the warnings. And regarding guest's comments, doesn't the Haskell 2010 standard[1] count as an "actual language standard"? If not, then what is it and why isn't it one?
[1] http://www.haskell.org/pipermail/haskell/2009-November/021750.html
Correct me if I'm wrong, but I thought 'HierarchicalModules' was an extension which codifies the 'Foo.Bar' import syntax (as opposed to 'import FooBar'), and didn't address allocation of functions to modules or naming issues like 'Char' vs 'Data.Char' or splitting 'Foreign' up or whatever. -- gwern

Gwern Branwen wrote:
wren ng thornton wrote:
I'm all for the warnings. And regarding guest's comments, doesn't the Haskell 2010 standard[1] count as an "actual language standard"? If not, then what is it and why isn't it one?
[1] http://www.haskell.org/pipermail/haskell/2009-November/021750.html
Correct me if I'm wrong, but I thought 'HierarchicalModules' was an extension which codifies the 'Foo.Bar' import syntax (as opposed to 'import FooBar'), and didn't address allocation of functions to modules or naming issues like 'Char' vs 'Data.Char' or splitting 'Foreign' up or whatever.
AFAIK, yes, the HierarchicalModules approval is just allowing dots in module names, rather than discussing what goes where. I was bringing haskell2010 up more to point out that the haskell98 standard is, officially, not up to date. Perhaps we should poke the haskell-prime committee to move the official location of standard functions for the haskell2011 standard? -- Live well, ~wren

Gwern Branwen wrote:
wren ng thornton wrote:
I'm all for the warnings. And regarding guest's comments, doesn't the Haskell 2010 standard[1] count as an "actual language standard"? If not, then what is it and why isn't it one?
[1] http://www.haskell.org/pipermail/haskell/2009-November/021750.html
Correct me if I'm wrong, but I thought 'HierarchicalModules' was an extension which codifies the 'Foo.Bar' import syntax (as opposed to 'import FooBar'), and didn't address allocation of functions to modules or naming issues like 'Char' vs 'Data.Char' or splitting 'Foreign' up or whatever.
AFAIK, yes, the HierarchicalModules approval is just allowing dots in module names, rather than discussing what goes where. I was bringing haskell2010 up more to point out that the haskell98 standard is, officially, not up to date. Perhaps we should poke the haskell-prime committee to move the official location of standard functions for the haskell2011 standard? -- Live well, ~wren

Hi,
In discussion with Gwern I've raised a bug in HLint to make using
Haskell 98 modules a warning. It's not the same as a formal
deprecation of those modules, but it's a step in that direction. I
think deprecating haskell98 modules is a reasonable step to do at some
point in the future, but I don't think that point has arrived yet (we
should at least publish Haskell 2010 first).
Thanks, Neil
2010/3/8 wren ng thornton
Gwern Branwen wrote:
wren ng thornton wrote:
I'm all for the warnings. And regarding guest's comments, doesn't the Haskell 2010 standard[1] count as an "actual language standard"? If not, then what is it and why isn't it one?
[1] http://www.haskell.org/pipermail/haskell/2009-November/021750.html
Correct me if I'm wrong, but I thought 'HierarchicalModules' was an extension which codifies the 'Foo.Bar' import syntax (as opposed to 'import FooBar'), and didn't address allocation of functions to modules or naming issues like 'Char' vs 'Data.Char' or splitting 'Foreign' up or whatever.
AFAIK, yes, the HierarchicalModules approval is just allowing dots in module names, rather than discussing what goes where. I was bringing haskell2010 up more to point out that the haskell98 standard is, officially, not up to date.
Perhaps we should poke the haskell-prime committee to move the official location of standard functions for the haskell2011 standard?
-- Live well, ~wren _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Neil Mitchell schrieb:
Hi,
In discussion with Gwern I've raised a bug in HLint to make using Haskell 98 modules a warning. It's not the same as a formal deprecation of those modules, but it's a step in that direction. I think deprecating haskell98 modules is a reasonable step to do at some point in the future, but I don't think that point has arrived yet (we should at least publish Haskell 2010 first).
Maybe Cabal (or HLint) could at least warn about mixed use of haskell98 and base modules, but this would be certainly a hack in Cabal.

On Mon, 8 Mar 2010, wren ng thornton wrote:
Gwern Branwen wrote:
See http://hackage.haskell.org/trac/hackage/ticket/640
It seems to me that a warning on using the 'haskell98' package wouldn't be a bad thing; those modules have since been split apart in better modules, the names are ever more unfamiliar, etc.
But Duncan thinks it merits discussion.
I'm all for the warnings. And regarding guest's comments, doesn't the Haskell 2010 standard[1] count as an "actual language standard"? If not, then what is it and why isn't it one?
Actually, when using GHCi I like to have the short Haskell98 module names. In contrast to that when writing a package for real use, that is, when I use Cabal, then Cabal might warn that the package haskell98 is deprecated. Even more deprecating a package by a Cabal field would be a nice thing and then haskell98 could be deprecated this way.

Henning Thielemann wrote:
Actually, when using GHCi I like to have the short Haskell98 module names.
I agree that the warning is less important in GHCi during the deprecation stage. However, for consistency, I think the Haskell98 names should go away by default in GHCi when they go away in GHC. You can always enable them manually if they are important to you. Or use dot-ghci and/or :def commands to save keystrokes when setting up your favorite GHCi environments. That is probably a better idea anyway. Regards, Yitz

And regarding guest's comments, doesn't the Haskell 2010 standard[1] count as an "actual language standard"? If not, then what is it and why isn't it one?
Haskell 2010 has been decided, but the Language Report itself has not yet been published. So yes, it is a standard, but not one you can refer to (yet). IIRC, H'2010 makes no changes to the Libraries section of the Report. There was a proposal for 2010 to update the names of the libraries, to their new hierarchical forms. It was not accepted. Thus, the Haskell'98 names are still part of the official 2010 language standard, if I am not mistaken. There has been discussion about whether the Language Report should mandate any particular libraries at all. No decision has yet been taken to remove the Libraries specification from the Report. Perhaps some of these issues should be resolved for Haskell 2011, and I encourage those interested to develop a proposal on the haskell- prime mailing list (which is open to all). Regards, Malcolm

On 09/03/2010 12:11, Malcolm Wallace wrote:
And regarding guest's comments, doesn't the Haskell 2010 standard[1] count as an "actual language standard"? If not, then what is it and why isn't it one?
Haskell 2010 has been decided, but the Language Report itself has not yet been published. So yes, it is a standard, but not one you can refer to (yet).
IIRC, H'2010 makes no changes to the Libraries section of the Report. There was a proposal for 2010 to update the names of the libraries, to their new hierarchical forms. It was not accepted. Thus, the Haskell'98 names are still part of the official 2010 language standard, if I am not mistaken.
The discussion didn't result in a concrete proposal, but there was general agreement that we should remove Directory System Time Locale CPUTime Random and update the others to use hierarchical names: 1. Ratio keep as Data.Ratio 2. Complex keep as Data.Complex 3. Numeric keep as Numeric (?) 4. Ix keep as Data.Ix 5. Array keep as Data.Array 6. List keep as Data.List 7. Maybe keep as Data.Maybe 8. Char keep as Data.Char 9. Monad keep as Control.Monad 10. IO keep as System.IO and the FFI libraries would be added as CError -> Foreign.C.Error CForeign -> Foreign.C CString -> Foreign.C.C.String CTypes -> Foreign.C.Types ForeignPtr -> Foreign.ForeignPtr Int -> Data.Int MarshalAlloc -> Foreign.Marshal.Alloc MarshalArray -> Foreign.Marshal.Array MarshalError -> Foreign.Marshal.Error MarshalUtils -> Foreign.Marshal.Utils StablePtr -> Foreign.StablePtr Storable -> Foreign.Storable Word -> Data.Word (this proposal wasn't discussed publicly, unfortunately. I think that was an oversight.) I was actually planning to look at doing this during the H2010 report update. However, updating the libraries in the report to use the hierarchical names actually gives us a slight problem, in that we then have to provide those modules with exactly those interfaces for ever, presumably via some well-known package. The module names overlap with base, so we'd have to do some package reorganisation. Things could get painful really fast. I'm tempted to not do this in H2010, but defer it until we've really thought about how to manage the transition and future updates. I would like to remove the old superseded modules though: Directory, Time, System, Random, Locale, CPUTime. That would be an easy change, and we can provide a haskell2010 package exporting just the remaining modules. Cheers, Simon

On Wed, Mar 17, 2010 at 9:48 AM, Simon Marlow
The discussion didn't result in a concrete proposal, but there was general agreement that we should remove
Directory System Time Locale CPUTime Random
and update the others to use hierarchical names:
1. Ratio keep as Data.Ratio 2. Complex keep as Data.Complex 3. Numeric keep as Numeric (?) 4. Ix keep as Data.Ix 5. Array keep as Data.Array 6. List keep as Data.List 7. Maybe keep as Data.Maybe 8. Char keep as Data.Char 9. Monad keep as Control.Monad 10. IO keep as System.IO
and the FFI libraries would be added as
CError -> Foreign.C.Error CForeign -> Foreign.C CString -> Foreign.C.C.String CTypes -> Foreign.C.Types ForeignPtr -> Foreign.ForeignPtr Int -> Data.Int MarshalAlloc -> Foreign.Marshal.Alloc MarshalArray -> Foreign.Marshal.Array MarshalError -> Foreign.Marshal.Error MarshalUtils -> Foreign.Marshal.Utils StablePtr -> Foreign.StablePtr Storable -> Foreign.Storable Word -> Data.Word
(this proposal wasn't discussed publicly, unfortunately. I think that was an oversight.)
I was actually planning to look at doing this during the H2010 report update. However, updating the libraries in the report to use the hierarchical names actually gives us a slight problem, in that we then have to provide those modules with exactly those interfaces for ever, presumably via some well-known package. The module names overlap with base, so we'd have to do some package reorganisation. Things could get painful really fast. I'm tempted to not do this in H2010, but defer it until we've really thought about how to manage the transition and future updates.
I would like to remove the old superseded modules though: Directory, Time, System, Random, Locale, CPUTime. That would be an easy change, and we can provide a haskell2010 package exporting just the remaining modules.
Cheers, Simon
How goes the removal of those old modules? -- gwern

Gwern Branwen schrieb:
See http://hackage.haskell.org/trac/hackage/ticket/640
It seems to me that a warning on using the 'haskell98' package wouldn't be a bad thing; those modules have since been split apart in better modules, the names are ever more unfamiliar, etc.
But Duncan thinks it merits discussion.
The modules in haskell98 are just wrapper modules providing their functions under different module names in order to support the (old) currently documented haskell98 standard from Dec. 2002 (also used in many teaching books). http://www.haskell.org/onlinelibrary/ This documentation lists even modules that are not part of current ghc installations like: module PreludeList, module PreludeText, module PreludeIO I don't miss these modules and I think we should eventually get rid of haskell98 as a *core* package of ghc (and the haskell-platform). Before omitting the haskell98 package we should warn about it! Whoever still wants to use the haskell98 package may install it via cabal (or use his/her own wrapper module(s)). I would at least warn about a haskell98 dependency in .cabal files. Maybe even a warning for every non-hierarchical module import should be issued. Cheers Christian

Please don't deprecate these modules. It is actively contributing to bitrot to deprecate a perfectly useful and well defined API. When I write new code that only needs C, I don't use C++ just because C is older. Likewise, when writing Haskell code today that doesn't require anything more than haskell 98, I use haskell 98. Because it is a well defined standard that I know will be supported by future and past compilers. Unlike writing to some current snapshot of what the libraries look like. Encouraging people to use bleeding edge APIs just contributes to the already dicey problem of writing future and backwards compatible code in Haskell, in fact, writing to haskell 98 is the _only_ option at the moment with any ability to do so. Haskell 98 should never be deprecated, because it is a stable, well defined standard that useful programs can be written to if someone chooses to do so and wants their code to have a chance of working down the road without having to continually keep changing it to keep up with libraries changes. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

I'm all for supporting the haskell98 *language* (aka "portable" haskell code) except wrt non-hierarchical module names. Without hierarchical module names cabal and hackage are unperceivable. In fact, the haskell98 modules are bit-rotten and the corresponding hierarchical modules (like Data.List) are certainly no "bleeding edge APIs", but the de-facto standard. Christian John Meacham schrieb:
Please don't deprecate these modules.
It is actively contributing to bitrot to deprecate a perfectly useful and well defined API. When I write new code that only needs C, I don't use C++ just because C is older. Likewise, when writing Haskell code today that doesn't require anything more than haskell 98, I use haskell 98. Because it is a well defined standard that I know will be supported by future and past compilers. Unlike writing to some current snapshot of what the libraries look like.
Encouraging people to use bleeding edge APIs just contributes to the already dicey problem of writing future and backwards compatible code in Haskell, in fact, writing to haskell 98 is the _only_ option at the moment with any ability to do so.
Haskell 98 should never be deprecated, because it is a stable, well defined standard that useful programs can be written to if someone chooses to do so and wants their code to have a chance of working down the road without having to continually keep changing it to keep up with libraries changes.
John

On Wed, Mar 10, 2010 at 7:56 PM, John Meacham
Please don't deprecate these modules.
It is actively contributing to bitrot to deprecate a perfectly useful and well defined API. When I write new code that only needs C, I don't use C++ just because C is older. Likewise, when writing Haskell code today that doesn't require anything more than haskell 98, I use haskell 98. Because it is a well defined standard that I know will be supported by future and past compilers. Unlike writing to some current snapshot of what the libraries look like.
Encouraging people to use bleeding edge APIs just contributes to the already dicey problem of writing future and backwards compatible code in Haskell, in fact, writing to haskell 98 is the _only_ option at the moment with any ability to do so.
Haskell 98 should never be deprecated, because it is a stable, well defined standard that useful programs can be written to if someone chooses to do so and wants their code to have a chance of working down the road without having to continually keep changing it to keep up with libraries changes.
John
No one is talking about removing haskell98; my bug report is about warning about use of it. You can go on using 'import Monad' if you like - just like you can go on shadowing variables, omitting pattern-matches & type sigs, naming unused variables, and defining unused functions. Just like with haskell98, there are (contrived and otherwise) scenarios where one actually wants to do those things, which is why they aren't *errors*. I don't think haskell98 meaningfully helps one write long-term code. Something that helps long-term code is explicit imports, for example, since it future-proofs one against added clashing function names and makes it vastly easier for future programmers to update imports and uses. But being able to write 'import List' versus 'import Data.List'? No, I don't see that at all. What, are functions like 'isInfixOf' going to be removed from Data.List though guaranteed to be in List? Nor do you address the multiple strikes against haskell98 that I've already adduced: that it encourages people (like you!) to duplicate library code; that it leads to mixture of modern and old module names (I'm not sure that I've yet run into a package which needed only haskell98 and not also 'base'); that it hides the finer-grained dependencies (reverse dependencies were linked; notice that each package that depends on haskell98 may be screwing up the reverse dependency list of process/random/containers/old-locale/...); etc. -- gwern

On Thu, Mar 11, 2010 at 09:59:11AM -0500, Gwern Branwen wrote:
No one is talking about removing haskell98; my bug report is about warning about use of it. You can go on using 'import Monad' if you like - just like you can go on shadowing variables, omitting pattern-matches & type sigs, naming unused variables, and defining unused functions. Just like with haskell98, there are (contrived and otherwise) scenarios where one actually wants to do those things, which is why they aren't *errors*.
Except that writing a program that just uses Haskell 98 is a virtue, not a vice. When you target a standard your program becomes much easier to maintain. As it is now, it is a major pain to write future compatible haskell. For instance, pretty much every ghc compiler release I have had to modify code due to one of the libraries suddenly exporting something it didn't before. Like you say, qualified imports can help with this, but it still doesn't protect against the meaning of functions changing and can be much harder to maintain. It doesn't matter whether that is unlikely or not, it is sometimes important to _know_ a program or library will continue to work in the future. If you are printing a book with Haskell code, or heck, just want to be able to publish it and not have to keep modifying it every time there is a new compiler release. Right now it is almost impossible to be 'done' with a Haskell program. you continually have to churn the dependency list and keep up with changes in ghc, targetting haskell 98 when possible gets rid of those issues completely. As will targetting Haskell 2010, or any other specific release. We should be _encouraging_ writing against standards when possible, not discouraging it. Haskell 98 may be aethetically displeasing in some ways, but that doesn't diminish its usefulness as a standard.
Nor do you address the multiple strikes against haskell98 that I've already adduced: that it encourages people (like you!) to duplicate library code; that it leads to mixture of modern and old module names (I'm not sure that I've yet run into a package which needed only haskell98 and not also 'base'); that it hides the finer-grained dependencies (reverse dependencies were linked; notice that each package that depends on haskell98 may be screwing up the reverse dependency list of process/random/containers/old-locale/...); etc.
One has to duplicate library code if one wants their program to be portable to libraries/versions of ghc that don't have said code in their library. Having newer packages depend on older, portable packages should not be a burden or force the portable packages to be needlessly changed. If this somehow is an issue, that seems like an issue with the package manager that needs to be addressed, not by the brute force approach of dragging everything to haskell-prime kicking and screaming. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On 12 Mar 2010, at 02:11, John Meacham wrote:
Except that writing a program that just uses Haskell 98 is a virtue, not a vice. When you target a standard your program becomes much easier to maintain. As it is now, it is a major pain to write future compatible haskell.
+1 from me. This is exactly the purpose of standards. If you have multiple overlapping standards, then perhaps it would make sense to deprecate some of them. But we are in the situation of having only two current standards ('98 and 2010), and they exactly agree on the contents of these libraries. Furthermore, the H'98 standard itself states It is intended to be a "stable" language in sense the implementors are committed to supporting Haskell 98 exactly as specified, for the foreseeable future. The base library package has no such guarantee - it is not supported in its entirety by all compilers, and it changes frequently. (As one data point, base changes frequently enough and severely enough to break my nightly builds of nhc98 several times a year.) In my view there is no way that base can be called stable yet. Regards, Malcolm

Hello,
I agree with John because I don't think that adding warnings about
using the haskell98 package achieves anything meaningful. The issue
seems to be a matter of taste---some people like it, some don't, and
we already have a system that lets us choose if we want to use it or
not. It certainly does not seem in the same class of problems as
"incomplete patterns in definitions", for example.
As far as indirect dependencies are concerned, I agree that it might
be nice to have more control over the packages on which we depend
(certainly important in the case of GPLd libraries) but that has
nothing to do with the haskell98 package.
-Iavor
PS: By the way, I don't see how hierarchical names are important in
any way to Cabal or hackage: I agree that using "." in module names
instead of, say, "_" might look a bit nicer (or just more familiar?)
but, as features go, this is a pretty small one.
On Thu, Mar 11, 2010 at 6:11 PM, John Meacham
On Thu, Mar 11, 2010 at 09:59:11AM -0500, Gwern Branwen wrote:
No one is talking about removing haskell98; my bug report is about warning about use of it. You can go on using 'import Monad' if you like - just like you can go on shadowing variables, omitting pattern-matches & type sigs, naming unused variables, and defining unused functions. Just like with haskell98, there are (contrived and otherwise) scenarios where one actually wants to do those things, which is why they aren't *errors*.
Except that writing a program that just uses Haskell 98 is a virtue, not a vice. When you target a standard your program becomes much easier to maintain. As it is now, it is a major pain to write future compatible haskell. For instance, pretty much every ghc compiler release I have had to modify code due to one of the libraries suddenly exporting something it didn't before. Like you say, qualified imports can help with this, but it still doesn't protect against the meaning of functions changing and can be much harder to maintain. It doesn't matter whether that is unlikely or not, it is sometimes important to _know_ a program or library will continue to work in the future. If you are printing a book with Haskell code, or heck, just want to be able to publish it and not have to keep modifying it every time there is a new compiler release. Right now it is almost impossible to be 'done' with a Haskell program. you continually have to churn the dependency list and keep up with changes in ghc, targetting haskell 98 when possible gets rid of those issues completely. As will targetting Haskell 2010, or any other specific release. We should be _encouraging_ writing against standards when possible, not discouraging it. Haskell 98 may be aethetically displeasing in some ways, but that doesn't diminish its usefulness as a standard.
Nor do you address the multiple strikes against haskell98 that I've already adduced: that it encourages people (like you!) to duplicate library code; that it leads to mixture of modern and old module names (I'm not sure that I've yet run into a package which needed only haskell98 and not also 'base'); that it hides the finer-grained dependencies (reverse dependencies were linked; notice that each package that depends on haskell98 may be screwing up the reverse dependency list of process/random/containers/old-locale/...); etc.
One has to duplicate library code if one wants their program to be portable to libraries/versions of ghc that don't have said code in their library. Having newer packages depend on older, portable packages should not be a burden or force the portable packages to be needlessly changed. If this somehow is an issue, that seems like an issue with the package manager that needs to be addressed, not by the brute force approach of dragging everything to haskell-prime kicking and screaming.
John
-- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/ _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 03/12/10 15:07, Iavor Diatchki wrote:
thanks Iavor!
I agree with John because I don't think that adding warnings about using the haskell98 package achieves anything meaningful.
Okay. Who likes importing "Data.List" and "Monad" in the same module? Anyone? (I'll believe it if you say yes, because I've an inkling of a reason in my head... but you'd better be a real person wanting that, not just a hypothetical.)
The issue seems to be a matter of taste---some people like it, some don't, and we already have a system that lets us choose if we want to use it or not.
Do you mean the .cabal file i.e. "don't depend on haskell98" ? If so, I daresay that is indeed a pretty good system. It's making it easier for Gwern to send patches to package authors he thinks might be sympathetic. (it's like a warning message, but generated by a human rather than a machine, and correspondingly smarter!)
It certainly does not seem in the same class of problems as "incomplete patterns in definitions", for example.
but it's nearer the class of -Wall warnings, some of which are for controversial points of style (such as type-signatures for every top-level definition). By the way, does anyone actually practice "only import with an explicit import list", and how often does *your* code break?
As far as indirect dependencies are concerned, I agree that it might be nice to have more control over the packages on which we depend (certainly important in the case of GPLd libraries) but that has nothing to do with the haskell98 package.
if you depend on haskell98, then you depend on: array, base, directory, old-locale, old-time, process, random (which indirectly depend on filepath and time, also.) Hmm. I was thinking it could be useful to have statistics on what portion of Hackage actually uses things like network, but that isn't included. I reckon "process" might be the most "interesting" of those deps, but, I don't know -- anyone want to advocate specifically? -Isaac

Okay. Who likes importing "Data.List" and "Monad" in the same module? Anyone? (I'll believe it if you say yes, because I've an inkling of a reason in my head... but you'd better be a real person wanting that, not just a hypothetical.)
I have a distinct preference to use the Haskell'98 module names when I can. Just occasionally, I need a function that was not available in the Haskell'98 libraries. On such occasions, I might tend to copy the definition locally into the application itself, rather than import from base. Even more occasionally, that is not possible, because the function cannot be defined in pure H'98. Examples include unsafeInterleaveIO, unsafeCoerce, etc. That is when I find myself importing e.g. List, Monad, and System.IO.Unsafe next to each other.
if you depend on haskell98, then you depend on: array, base, directory, old-locale, old-time, process, random (which indirectly depend on filepath and time, also.)
As I frequently point out, those dependencies only apply to the ghc compiler. With other compilers, e.g. nhc98, the haskell'98 libraries underlie all the others. Base depends on haskell98, not the other way round. I still believe that ghc made a mistake in turning the dependencies the wrong way. In my opinion, it is one of the main causes of frequent breakage of libraries/apps that depend on base, and of the inability to upgrade base in any given version of ghc. Regards, Malcolm

On Fri, Mar 12, 2010 at 09:23:46PM +0000, Malcolm Wallace wrote:
if you depend on haskell98, then you depend on: array, base, directory, old-locale, old-time, process, random (which indirectly depend on filepath and time, also.)
As I frequently point out, those dependencies only apply to the ghc compiler. With other compilers, e.g. nhc98, the haskell'98 libraries underlie all the others. Base depends on haskell98, not the other way round. I still believe that ghc made a mistake in turning the dependencies the wrong way. In my opinion, it is one of the main causes of frequent breakage of libraries/apps that depend on base, and of the inability to upgrade base in any given version of ghc.
jhc actually has another system, where base and haskell98 both depend on 'jhc' which underlys everything. Or, that is the goal at least, I originally copied ghc's design for 'base' but have been moving away to something more logical given jhc's somewhat different library implementation. The transition isn't complete though. The general idea for compatibility with other compilers (including other versions of jhc) is to use the ability for jhc libraries to re-export modules under different names. for instance, haskell98 will probably do something like export Compat.Haskell98.Prelude as Prelude export Compat.Haskell98.List as List and haskell98 will be more of an 'interface specification' than a packaget itself. likewise I could have something like ghc-base4 (to give compatability with ghc's base-4.x that does as export Compat.Haskell98.Prelude as Prelude export Compat.Base4.Data.List as Data.List now, module names are resolved lazily (like function names in haskell code) so the fact that ghc-base4 and haskell98 both export Prelude doesn't hurt, since they both export the same underlying Prelude there is no conflict, this is in contrast to creating a dummy module that just re-exports an entire other module as we currently see in ghc's haskell98 package. A different module in the same program can even use 'haskell2020' and they will still link together, each module using the appropriate imports for which it was written. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On 12/03/2010 21:23, Malcolm Wallace wrote:
Okay. Who likes importing "Data.List" and "Monad" in the same module? Anyone? (I'll believe it if you say yes, because I've an inkling of a reason in my head... but you'd better be a real person wanting that, not just a hypothetical.)
I have a distinct preference to use the Haskell'98 module names when I can. Just occasionally, I need a function that was not available in the Haskell'98 libraries. On such occasions, I might tend to copy the definition locally into the application itself, rather than import from base. Even more occasionally, that is not possible, because the function cannot be defined in pure H'98. Examples include unsafeInterleaveIO, unsafeCoerce, etc. That is when I find myself importing e.g. List, Monad, and System.IO.Unsafe next to each other.
if you depend on haskell98, then you depend on: array, base, directory, old-locale, old-time, process, random (which indirectly depend on filepath and time, also.)
As I frequently point out, those dependencies only apply to the ghc compiler. With other compilers, e.g. nhc98, the haskell'98 libraries underlie all the others. Base depends on haskell98, not the other way round. I still believe that ghc made a mistake in turning the dependencies the wrong way. In my opinion, it is one of the main causes of frequent breakage of libraries/apps that depend on base, and of the inability to upgrade base in any given version of ghc.
Well, I think the right way would be for both packages to depend on an another package, as jhc has done. But I do think that having base depend on haskell98 is definitely the wrong way, since the goal is ultimately to move away from the non-hierarchical names. Having them baked into the root of the dependency tree makes it really hard to get rid of them. That's the reason I went with base<-haskell98: with a view to eventually dropping the non-hierarchical names, and that's the point that originally started the thread, right? Even if we drop the haskell98 dependency from as many packages as we can find, in nhc98 it'll still be lurking right at the root of the tree, whereas in GHC you can be sure it's not polluting your name space or dragging in ancient deprecated libraries (e.g. Time). Cheers, Simon

John Meacham wrote:
Please don't deprecate these modules. It is actively contributing to bitrot to deprecate a perfectly useful and well defined API.
I think "deprecate" is just the wrong word. Gwern is not saying that we should remove haskell98 from Hackage, nor remove the -98 flag from Hugs, nor build a special case into compilers that make modules not compile if they use Haskell 98 syntax. As I understand it, the problem he is trying to solve is the following: Haskell code today uses hierarchical module names almost universally. This has been the case for years. Yet a huge number of packages on Hackage directly or indirectly depend on the the haskell98 module, whose sole purpose is to allow the old non-hierarchical module names from pre-addendum Haskell 98. Gwern is just trying to think of a way to remove all of those spurious dependencies. I agree that this cleanup would be a good idea. The only question is, how do we best go about it? Or have I misunderstood? Thanks, Yitz

On Thu, Mar 11, 2010 at 10:00 AM, Yitzchak Gale
John Meacham wrote:
Please don't deprecate these modules. It is actively contributing to bitrot to deprecate a perfectly useful and well defined API.
I think "deprecate" is just the wrong word. Gwern is not saying that we should remove haskell98 from Hackage, nor remove the -98 flag from Hugs, nor build a special case into compilers that make modules not compile if they use Haskell 98 syntax.
As I understand it, the problem he is trying to solve is the following:
Haskell code today uses hierarchical module names almost universally. This has been the case for years. Yet a huge number of packages on Hackage directly or indirectly depend on the the haskell98 module, whose sole purpose is to allow the old non-hierarchical module names from pre-addendum Haskell 98.
Gwern is just trying to think of a way to remove all of those spurious dependencies. I agree that this cleanup would be a good idea. The only question is, how do we best go about it?
Or have I misunderstood?
Thanks, Yitz
Seems reasonable. Besides asking for a warning in Cabal (the logical place, since GHC is too low-level and doesn't handle module/package-level stuff), Neil has already mentioned that hlint will warn about haskell98 module names, and I have been sending in patches removing haskell98 deps - the fewer users of haskell98 there are, the less the cost of adding such a warning. With a three-pronged approach, the pain should be as minimal as possible. -- gwern

On 2010-03-11, Yitzchak Gale
John Meacham wrote:
Please don't deprecate these modules. It is actively contributing to bitrot to deprecate a perfectly useful and well defined API.
I think "deprecate" is just the wrong word. Gwern is not saying that we should remove haskell98 from Hackage, nor remove the -98 flag from Hugs, nor build a special case into compilers that make modules not compile if they use Haskell 98 syntax.
It is precisely the right word -- in the context of computer standards it means discouraging use due to new ways of accomplishing the same thing, while still allowing it. Doing any of those things you mentioned would not be deprecation, but breaking.
As I understand it, the problem he is trying to solve is the following:
I don't see why it's a problem, frankly.
Haskell code today uses hierarchical module names almost universally. This has been the case for years.
Check and check.
Yet a huge number of packages on Hackage directly or indirectly depend on the the haskell98 module, whose sole purpose is to allow the old non-hierarchical module names from pre-addendum Haskell 98.
In other words, to _implement the standard_. Some people do code to the standard as much as practicable, because that portion is then guaranteed to work, leaving only uncertainties about the portions that aren't Haskell 98. If you want to instead throw their code on a treadmill of evolving "what works as of GHC-HEAD", then you have to be the maintainer.
Gwern is just trying to think of a way to remove all of those spurious dependencies. I agree that this cleanup would be a good idea. The only question is, how do we best go about it?
I don't see how it's a _useful_ cleanup, or that the dependencies are truly spurious. -- Aaron Denney -><-

On Fri, Mar 12, 2010 at 5:43 PM, Aaron Denney
On 2010-03-11, Yitzchak Gale
wrote: John Meacham wrote:
Please don't deprecate these modules. It is actively contributing to bitrot to deprecate a perfectly useful and well defined API.
I think "deprecate" is just the wrong word. Gwern is not saying that we should remove haskell98 from Hackage, nor remove the -98 flag from Hugs, nor build a special case into compilers that make modules not compile if they use Haskell 98 syntax.
It is precisely the right word -- in the context of computer standards it means discouraging use due to new ways of accomplishing the same thing, while still allowing it. Doing any of those things you mentioned would not be deprecation, but breaking.
As I understand it, the problem he is trying to solve is the following:
I don't see why it's a problem, frankly.
Haskell code today uses hierarchical module names almost universally. This has been the case for years.
Check and check.
Yet a huge number of packages on Hackage directly or indirectly depend on the the haskell98 module, whose sole purpose is to allow the old non-hierarchical module names from pre-addendum Haskell 98.
In other words, to _implement the standard_. Some people do code to the standard as much as practicable, because that portion is then guaranteed to work, leaving only uncertainties about the portions that aren't Haskell 98. If you want to instead throw their code on a treadmill of evolving "what works as of GHC-HEAD", then you have to be the maintainer.
Gwern is just trying to think of a way to remove all of those spurious dependencies. I agree that this cleanup would be a good idea. The only question is, how do we best go about it?
I don't see how it's a _useful_ cleanup, or that the dependencies are truly spurious.
You haven't been paying attention then, or you're using a different definition of 'spurious' than I am. *Many* packages do not use haskell98! I'm pretty sure I've said this already. I have sent in multiple patches which consisted solely of one line removing haskell98 from the .cabal because the haskell98 modules *were not imported*. I don't know how a dependency can be more spurious than that. -- gwern

On Fri, Mar 12, 2010 at 08:44:46PM -0500, Gwern Branwen wrote:
multiple patches which consisted solely of one line removing haskell98 from the .cabal because the haskell98 modules *were not imported*.
A general "Nothing from dependency is imported" warning would be great, but trickier to implement. It's a similar problem to implementing an "extension isn't used" warning. Thanks Ian

On Sat, Mar 13, 2010 at 11:06 AM, Ian Lynagh
On Fri, Mar 12, 2010 at 08:44:46PM -0500, Gwern Branwen wrote:
multiple patches which consisted solely of one line removing haskell98 from the .cabal because the haskell98 modules *were not imported*.
A general "Nothing from dependency is imported" warning would be great, but trickier to implement. It's a similar problem to implementing an "extension isn't used" warning.
Thanks Ian
I've opened a ticket for this: http://hackage.haskell.org/trac/hackage/ticket/643 It's independent of the general issue though. -- gwern

On Mar 14, 2010, at 17:55 , Gwern Branwen wrote:
On Sat, Mar 13, 2010 at 11:06 AM, Ian Lynagh
wrote: On Fri, Mar 12, 2010 at 08:44:46PM -0500, Gwern Branwen wrote:
multiple patches which consisted solely of one line removing haskell98 from the .cabal because the haskell98 modules *were not imported*.
A general "Nothing from dependency is imported" warning would be great, but trickier to implement. It's a similar problem to implementing an "extension isn't used" warning.
I've opened a ticket for this: http://hackage.haskell.org/trac/hackage/ticket/643
Actually, doesn't the instances-are-global thing make this essentially impossible without whole-program analysis? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On 03/14/10 22:11, Brandon S. Allbery KF8NH wrote:
On Mar 14, 2010, at 17:55 , Gwern Branwen wrote:
On Sat, Mar 13, 2010 at 11:06 AM, Ian Lynagh
wrote: On Fri, Mar 12, 2010 at 08:44:46PM -0500, Gwern Branwen wrote:
multiple patches which consisted solely of one line removing haskell98 from the .cabal because the haskell98 modules *were not imported*.
A general "Nothing from dependency is imported" warning would be great, but trickier to implement. It's a similar problem to implementing an "extension isn't used" warning.
I've opened a ticket for this: http://hackage.haskell.org/trac/hackage/ticket/643
Actually, doesn't the instances-are-global thing make this essentially impossible without whole-program analysis?
GHC will not find an instance that's never imported, I believe. Therefore dependencies that are nowhere imported can always be safely removed. Is this right? -Isaac

On Sun, Mar 14, 2010 at 10:19 PM, Isaac Dupree
On 03/14/10 22:11, Brandon S. Allbery KF8NH wrote:
On Mar 14, 2010, at 17:55 , Gwern Branwen wrote:
On Sat, Mar 13, 2010 at 11:06 AM, Ian Lynagh
wrote: On Fri, Mar 12, 2010 at 08:44:46PM -0500, Gwern Branwen wrote:
multiple patches which consisted solely of one line removing haskell98 from the .cabal because the haskell98 modules *were not imported*.
A general "Nothing from dependency is imported" warning would be great, but trickier to implement. It's a similar problem to implementing an "extension isn't used" warning.
I've opened a ticket for this: http://hackage.haskell.org/trac/hackage/ticket/643
Actually, doesn't the instances-are-global thing make this essentially impossible without whole-program analysis?
GHC will not find an instance that's never imported, I believe. Therefore dependencies that are nowhere imported can always be safely removed. Is this right?
-Isaac
I would be rather surprised if it were not true! -- gwern

On Mon, Mar 15, 2010 at 3:19 AM, Isaac Dupree
On 03/14/10 22:11, Brandon S. Allbery KF8NH wrote:
On Mar 14, 2010, at 17:55 , Gwern Branwen wrote:
On Sat, Mar 13, 2010 at 11:06 AM, Ian Lynagh
wrote: On Fri, Mar 12, 2010 at 08:44:46PM -0500, Gwern Branwen wrote:
multiple patches which consisted solely of one line removing haskell98 from the .cabal because the haskell98 modules *were not imported*.
A general "Nothing from dependency is imported" warning would be great, but trickier to implement. It's a similar problem to implementing an "extension isn't used" warning.
I've opened a ticket for this: http://hackage.haskell.org/trac/hackage/ticket/643
Actually, doesn't the instances-are-global thing make this essentially impossible without whole-program analysis?
GHC will not find an instance that's never imported, I believe. Therefore dependencies that are nowhere imported can always be safely removed. Is this right?
No, there are packages that instead of exporting modules, export C header files like bindings-DSL for example: http://hackage.haskell.org/package/bindings-DSL Removing such a dependency will break your build if you #include these header files. However, maybe bindings-DSL is the only example of this type of package. regards, Bas

I wrote:
I think "deprecate" is just the wrong word. Gwern is not saying that we should remove haskell98 from Hackage, nor remove the -98 flag from Hugs, nor build a special case into compilers that make modules not compile if they use Haskell 98 syntax.
Aaron Denney wrote:
It is precisely the right word -- in the context of computer standards it means discouraging use due to new ways of accomplishing the same thing, while still allowing it. Doing any of those things you mentioned would not be deprecation, but breaking.
Sorry I was unclear. The word "deprecate" has taken on a more precise technical meaning in some contexts. It means the first in a two-or-more-step process of removing a feature. Instead of abruptly replacing an old feature with a new one, you gradually make the new feature more available and the old feature less available from version to version, until finally the old feature is completely removed. That is the sense in which I was understanding the word. In my opinion, Haskell needs better-defined deprecation processes, both for Cabal and for Haskell Prime. That would help reduce some of the pain people have been describing in this thread. Regards, Yitz

On Mon, Mar 8, 2010 at 11:22 AM, Gwern Branwen
See http://hackage.haskell.org/trac/hackage/ticket/640
It seems to me that a warning on using the 'haskell98' package wouldn't be a bad thing; those modules have since been split apart in better modules, the names are ever more unfamiliar, etc.
But Duncan thinks it merits discussion.
While removing haskell98 from packages last night, I found a few more reasons to dislike it: * it masks a whole grab-bag of split-base dependencies: random, process, directory, old-locale, old-time, containers... * 'import System' is extremely opaque - is the person using System.Exit, System.Process, System.Environment or what? * the exported haskell98 modules are out of date; I found Meachem re-defining the functions repeatM and repeatM_ because a DrIFT module imported Monad rather than Control.Monad. -- gwern

For what's worth, here's the list of packages on hackage which depend on haskell98: http://bifunctor.homelinux.net/~roel/cgi-bin/hackage-scripts/revdeps/haskell... regards, Bas
participants (16)
-
Aaron Denney
-
Bas van Dijk
-
Brandon S. Allbery KF8NH
-
Christian Maeder
-
Gwern Branwen
-
Henning Thielemann
-
Henning Thielemann
-
Ian Lynagh
-
Iavor Diatchki
-
Isaac Dupree
-
John Meacham
-
Malcolm Wallace
-
Neil Mitchell
-
Simon Marlow
-
wren ng thornton
-
Yitzchak Gale