
I am not sure if this has been mentioned before, but something I would really find useful is the ability to tell Haskell to export everything in a function except for some named functions.
No one has responded so I thought I would make a suggestion about what the syntax might look like to do this. Currently the syntax to set what gets exports is:
module Module ( list, of, things, to, export ) where .... and to hide things on import is import Module hiding ( list, of, things, not, to, import )
How about combining the two (since 'hiding' is already a reserved word):
module Module hiding ( list, of, things, not, to, export ) where ....
Everything gets exported except what you explicitly hide. Is this general enough? Are there reasons why this might not work? And does this solve your problem? Does anyone like this idea (aethestically and pragmatically)? Jared.

Jared,
How about combining the two (since 'hiding' is already a reserved word):
module Module hiding ( list, of, things, not, to, export ) where ....
Everything gets exported except what you explicitly hide. Is this general enough? Are there reasons why this might not work? And does this solve your problem? Does anyone like this idea (aethestically and pragmatically)?
This seems to make perfect sense to me, by having this syntax we can cater for three different exports: export explicit functions only; export everything in the module and export everything except explicitly named functions. Thanks. Chris.
Jared.
Christopher Brown Ph.D. Student University of Kent. UK. http://www.cs.kent.ac.uk/people/rpg/cmb21/index.html

on this note, I thought it would be nice to do a 'mostly unqualified' import. import Foo qualified(foo,bar) which will have the effect of import Foo hiding(foo,bar) import qualified Foo(foo,bar) since usually you can import a whole module unqualified except for a few troublemakers. John -- John Meacham - ⑆repetae.net⑆john⑈

Am Dienstag, 21. Februar 2006 04:41 schrieb John Meacham:
on this note, I thought it would be nice to do a 'mostly unqualified' import.
import Foo qualified(foo,bar)
which will have the effect of
import Foo hiding(foo,bar) import qualified Foo(foo,bar)
since usually you can import a whole module unqualified except for a few troublemakers.
John
On the other hand, sometimes it makes sense to have a "mostly qualified" import. For example, if you import Data.Set or Data.Map you might want only the type constructors to be imported unqualified and the rest to be imported qualified. Best wishes, Wolfgang

Wolfgang Jeltsch
On the other hand, sometimes it makes sense to have a "mostly qualified" import. For example, if you import Data.Set or Data.Map you might want only the type constructors to be imported unqualified and the rest to be imported qualified.
Personally, I would greatly prefer to have libraries that do not clash with common Prelude functions. I find it quite annoying to always have to import these modules twice, and still have to qualify many uses. If you always have to qualify it, what's the advantage of Data.Set.empty over emptySet again? At least with 'emptySet' I know what to grep for. -k -- If I haven't seen further, it is by standing in the footprints of giants

Ketil Malde
Personally, I would greatly prefer to have libraries that do not clash with common Prelude functions.
Slightly related in spirit: Often additions to the language tends to change the meaning of existing programs: Implicit parameters broke programs using ? as an infix operator, Template Haskell breaks expressions with $, the proposed labelling scheme will (in all probability) break #. Perhaps this is unavoidable - there are only so many symbols in ASCII, and perhaps it is just too convenient to reuse them. (Perhaps it would be better to always require whitespace after symbolic infix operators?) -k -- If I haven't seen further, it is by standing in the footprints of giants

Am Dienstag, 21. Februar 2006 22:10 schrieb Ketil Malde:
[...]
Template Haskell breaks expressions with $,
It's very bad that with TH enabled you cannot write sections of the form ($ x) anymore which are sometimes very handy.
[...]
(Perhaps it would be better to always require whitespace after symbolic infix operators?)
Of course, this wouldn't help with the above-mentioned TH-related problem.
[...]
-k
-w

Am Dienstag, 21. Februar 2006 21:59 schrieb Ketil Malde:
Wolfgang Jeltsch
writes: On the other hand, sometimes it makes sense to have a "mostly qualified" import. For example, if you import Data.Set or Data.Map you might want only the type constructors to be imported unqualified and the rest to be imported qualified.
Personally, I would greatly prefer to have libraries that do not clash with common Prelude functions.
I would solve this problem by reducing the Prelude to just a core. List function could go, for example, (mostly) into Data.List.
I find it quite annoying to always have to import these modules twice, and still have to qualify many uses.
If you always have to qualify it, what's the advantage of Data.Set.empty over emptySet again? At least with 'emptySet' I know what to grep for.
I would import Data.Set as Set. So I would use Set.empty instead of emptySet. The advantage is that Set.empty is more structured. You can easily distinguish the kind of operation (empty) and the type you are working with (Set).
-k
-w

Wolfgang Jeltsch
I would solve this problem by reducing the Prelude to just a core. List function could go, for example, (mostly) into Data.List.
There is a proposal to shrink the prelude to the minimum possible. I have just fleshed out some of the details, at the bottom of this page: http://hackage.haskell.org/trac/haskell-prime/wiki/Prelude Here are the details, reproduced for email discussion: Let the Prelude itself contain only entities that relate purely to functions - no other datatypes. module Prelude ( (->) , (.) , ($) , ($!) , flip , id , const , error , undefined , seq , asTypeOf ) Everything else that is currently in the Haskell'98 Prelude is re-distributed across a variety of small modules. Where a syntactic desugaring rule currently uses an entity from the Prelude, the new interpretation is that it uses whatever binding of that entity is in scope - if there is no such entity in scope, it is an error. For compatibility, we define a wrapper module called Prelude.Standard which re-exports the original Haskell'98 Prelude: module Prelude.Standard ( module Prelude , module Prelude.Num , module Prelude.Comparison , module Prelude.Monad , module Prelude.List , module Prelude.Maybe , module Prelude.Either , module Prelude.Tuple , module Prelude.IO , module Prelude.Text ) And here are the individual fragments: module Prelude.Num ( data Natural(..) , data Int(..) , data Int8(..) , data Int16(..) , data Int32(..) , data Int64(..) , data Word8(..) , data Word16(..) , data Word32(..) , data Word64(..) , data Integer(..) , data Float(..) , data Double(..) , type Rational , class Integral(..) , class Num(..) , class Fractional(..) , class Real(..) , class RealFrac(..) , class Floating(..) , class RealFloat(..) , gcd, lcm , fromIntegral, realToFrac , numericEnumFrom, numericEnumFromTo, numericEnumFromThen , numericEnumFromThenTo , (^), (^^), (%) , even, odd, subtract ) module Prelude.Comparison ( data Bool(..) , data Ordering(..) , class Eq(..) , class Ord(..) , class Enum(..) , class Bounded(..) , otherwise , (&&), (||), not, until ) module Prelude.Monad ( class Functor(..) , class Monad(..) , mapM, mapM_, sequence, sequence_, (=<<) ) module Prelude.List ( data [](..) , all, and, any, (++), break, concat, concatMap, cycle, drop, dropWhile , elem, filter, foldl, foldl1, foldr, foldr1, head, (!!), init, iterate , last, length, lines, lookup, map, maximum, minimum, notElem, null , or, product, repeat, replicate, reverse, scanl, scanl1, scanr, scanr1 , span, splitAt, sum, tail, take, takeWhile, unlines, unwords, words ) module Prelude.Maybe ( data Maybe(..) , maybe ) module Prelude.Either ( data Either(..) , either ) module Prelude.Tuple ( data ()(..) , data (,)(..) , data (,,)(..) , data (,,,)(..) , data (,,,,)(..) , data (,,,,,)(..) , data (,,,,,,)(..) , data (,,,,,,,)(..) , data (,,,,,,,,)(..) , data (,,,,,,,,,)(..) , data (,,,,,,,,,,)(..) , data (,,,,,,,,,,,)(..) , data (,,,,,,,,,,,,)(..) , data (,,,,,,,,,,,,,)(..) , data (,,,,,,,,,,,,,,)(..) , fst, snd , unzip, unzip3, zip, zip3, zipWith, zipWith3 , curry, uncurry ) module Prelude.IO ( data IO , data IOError(..) , data FilePath , ioError, userError, catch , print , putChar, putStr, putStrLn , getChar, getLine, getContents, interact , readFile, writeFile, appendFile, readIO, readLn ) module Prelude.Text ( data Char(..) , type String , class Read(..) , class Show(..) , type ReadS , type ShowS , read, reads, readParen, lex , shows, showString, showParen, showChar )

Am Mittwoch, 22. Februar 2006 18:12 schrieb Malcolm Wallace:
[...]
module Prelude.Standard ( module Prelude , module Prelude.Num , module Prelude.Comparison , module Prelude.Monad , module Prelude.List , module Prelude.Maybe , module Prelude.Either , module Prelude.Tuple , module Prelude.IO , module Prelude.Text )
Why Prelude.List, not Data.List, etc.?
[...]
Best wishes, Wolfgang

Wolfgang Jeltsch
module Prelude.Standard ( module Prelude , module Prelude.Num , module Prelude.Comparison , module Prelude.Monad , module Prelude.List , module Prelude.Maybe , module Prelude.Either , module Prelude.Tuple , module Prelude.IO , module Prelude.Text )
Why Prelude.List, not Data.List, etc.?
No particular reason. Either choice would be good. (But I didn't want to imply that everything currently in Data.List would be re-exported, since it defines more than just Prelude entities.) Regards, Malcolm

On Wed, Feb 22, 2006 at 05:12:47PM +0000, Malcolm Wallace wrote:
Everything else that is currently in the Haskell'98 Prelude is re-distributed across a variety of small modules. Where a syntactic desugaring rule currently uses an entity from the Prelude, the new interpretation is that it uses whatever binding of that entity is in scope - if there is no such entity in scope, it is an error. For compatibility, we define a wrapper module called Prelude.Standard which re-exports the original Haskell'98 Prelude:
module Prelude.Standard ( module Prelude , module Prelude.Num , module Prelude.Comparison , module Prelude.Monad , module Prelude.List , module Prelude.Maybe , module Prelude.Either , module Prelude.Tuple , module Prelude.IO , module Prelude.Text )
It would be nice if there was an easy way to import an entire Haskell98 prelude hiding only Prelude.List.* stuff (for example). This would be possible if all Prelude.* modules would be imported automatically, but I guess it's not what you propose. Best regards Tomasz -- I am searching for programmers who are good at least in (Haskell || ML) && (Linux || FreeBSD || math) for work in Warsaw, Poland

On 2006-02-21, Wolfgang Jeltsch
Am Dienstag, 21. Februar 2006 04:41 schrieb John Meacham:
on this note, I thought it would be nice to do a 'mostly unqualified' import.
import Foo qualified(foo,bar)
which will have the effect of
import Foo hiding(foo,bar) import qualified Foo(foo,bar)
since usually you can import a whole module unqualified except for a few troublemakers.
John
On the other hand, sometimes it makes sense to have a "mostly qualified" import. For example, if you import Data.Set or Data.Map you might want only the type constructors to be imported unqualified and the rest to be imported qualified.
import qualified Foo unqualify1 = Foo.unqualify1 unqualify2 = Foo.unqualify2 ... (That is, this is already pretty easy to do.) -- Aaron Denney -><-

That seems sensible to me.
- Cale
On 20/02/06, Jared Updike
I am not sure if this has been mentioned before, but something I would really find useful is the ability to tell Haskell to export everything in a function except for some named functions.
No one has responded so I thought I would make a suggestion about what the syntax might look like to do this. Currently the syntax to set what gets exports is:
module Module ( list, of, things, to, export ) where .... and to hide things on import is import Module hiding ( list, of, things, not, to, import )
How about combining the two (since 'hiding' is already a reserved word):
module Module hiding ( list, of, things, not, to, export ) where ....
Everything gets exported except what you explicitly hide. Is this general enough? Are there reasons why this might not work? And does this solve your problem? Does anyone like this idea (aethestically and pragmatically)?
Jared.

"Jared Updike"
I am not sure if this has been mentioned before, but something I would really find useful is the ability to tell Haskell to export everything in a function except for some named functions.
No one has responded so ...
I believe some people (perhaps on another list) have been advocating the addition of Java-style public/private modifiers on function definitions, to indicate whether they are exported or not. (A truly horrible idea in my opinion!)
module Module hiding ( list, of, things, not, to, export ) where ....
I quite like this for its minimal syntactic overhead, and backward compatibility. There is a slight worry that it would be too easy to overlook the "hiding" keyword when reading a module, leading to confusion. There is also the issue that we might adopt the proposal to allow (and perhaps eventually, to require) type signatures on export lists. If so, then it would be kind of ridiculous to have interface signatures only for the things you are /not/ exporting! Regards, Malcolm

On 21/02/06, Malcolm Wallace
There is also the issue that we might adopt the proposal to allow (and perhaps eventually, to require) type signatures on export lists. If so, then it would be kind of ridiculous to have interface signatures only for the things you are /not/ exporting!
Regards, Malcolm
Of course, why would we require type signatures on hiding lists? :) They would just have to be treated differently. Of course, I could ask the same question about export lists, but I'm not sure if that is worth starting up at this point. ;) - Cale

"Jared Updike"
wrote: I am not sure if this has been mentioned before, but something I would really find useful is the ability to tell Haskell to export everything in a function except for some named functions.
No one has responded so ...
I believe some people (perhaps on another list) have been advocating the addition of Java-style public/private modifiers on function definitions, to indicate whether they are exported or not. (A truly horrible idea in my opinion!) Why is it horrible? It avoids redundancy in the code-file which is a good
On Tuesday 21 February 2006 11:40, Malcolm Wallace wrote: thing in general.
module Module hiding ( list, of, things, not, to, export ) where ....
I quite like this for its minimal syntactic overhead, and backward compatibility. There is a slight worry that it would be too easy to overlook the "hiding" keyword when reading a module, leading to confusion.
I dislike this idea because the export list is a sort of signature of the module, which is also often used for structuring the haddock documentation. In case of hiding() version you explicitly state the unimportant parts. Apart from that you might change the hidden functions much more often than the public interface. Proper signatures would be a nice solution I guess. Just my 2p! Regards, Georg
There is also the issue that we might adopt the proposal to allow (and perhaps eventually, to require) type signatures on export lists. If so, then it would be kind of ridiculous to have interface signatures only for the things you are /not/ exporting!
Regards, Malcolm _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime

On Tue, Feb 21, 2006 at 10:40:55AM +0000, Malcolm Wallace wrote:
There is also the issue that we might adopt the proposal to allow (and perhaps eventually, to require) type signatures on export lists.
All I have to say is "please, no" to the requiring part that is. I totally think type signatures in export lists should be allowed optionally with the exact same meaning as if they were specified at the top level within the module. I also like the export hiding idea, mainly for consistancy, it seems like something I'd expect to work and be surprised if it didn't even if I wouldn't use it a whole lot. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham
Malcolm Wallace wrote:
There is also the issue that we might adopt the proposal to allow (and perhaps eventually, to require) type signatures on export lists.
All I have to say is "please, no" to the requiring part that is.
I don't seriously propose for haskell-prime that signatures should be required on exports. Just permitting them would be a large and useful step up already. But the argument about whether to specify a module interface completely and explicitly in the source file might arise again in the next standardisation process, where I can see the balance might tip more in favour of compulsion.
I totally think type signatures in export lists should be allowed optionally with the exact same meaning as if they were specified at the top level within the module.
At the moment, only one type signature is permitted per entity (except for FFI foreign exports, where the exported signature may be more specific than the definitional signature). My proposal is that the normal export list can have signatures /in addition to/ the definitional signature, but that if there are thus two signatures for an entity, they must be identical. This is to prevent the case where one modifies the definition of the function, making it more general, but forgets to modify the corresponding export. Regards, Malcolm

Malcolm Wallace wrote:
... but that if there are thus two signatures for an entity, they must be identical. This is to prevent the case where one modifies the definition of the function, making it more general, but forgets to modify the corresponding export.
Sounds like the perfect example to illustrate the point that information shouldn't be doubled in the first place. Can you say why you want the type in the export list? Or really, why you want an export list at all? Presumably because it constitutes the module's "interface", but it is an ad-hoc thing (one interface per module). We already have the concept of "type class" which gives us re-usable interfaces. Isn't that much better? I was discussing that in (the second paragraph of): http://www.haskell.org//pipermail/haskell-prime/2006-January/000230.html Respectfully submitted, -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------

Johannes Waldmann
Sounds like the perfect example to illustrate the point that information shouldn't be doubled in the first place.
Yes, I suppose one could argue that.
Can you say why you want the type in the export list?
As a compact description of the module interface. Many people already do it, except that the signature is in a comment, and therefore not checked.
Or really, why you want an export list at all?
An explicit interface would be useful for many purposes besides machine-checked documentation. For instance, it could be used to eliminate the hs-boot or hi-boot files used by some compilers when dealing with recursive modules.
Presumably because it constitutes the module's "interface", but it is an ad-hoc thing (one interface per module). We already have the concept of "type class" which gives us re-usable interfaces. Isn't that much better?
The near correspondence between type classes, modules, and records, is well-known, yet still they are separate concepts in Haskell. Perhaps one day they will be merged. However, in the meantime, for both records and classes one is forced to give a signature to the contained elements/methods. For consistency, modules should do the same... Regards, Malcolm

Malcolm Wallace wrote:
An explicit interface would be useful for many purposes besides machine-checked documentation.
I don't see why you need the signature in two places (at the point at declaration and in the export list) for that. Do you want the compiler to check conformance (of the implementation with the exported type)? Then you probably designed the interface (export list) separately from the implementation, so they should not be both in one file.
For instance, it could be used to eliminate the hs-boot or hi-boot files used by some compilers when dealing with recursive modules.
Isn't this problem just *created* by the current export mechanism? See this comment http://www.haskell.org//pipermail/haskell/2006-February/017590.html Best regards, -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------

Malcolm Wallace wrote:
An explicit interface would be useful for many purposes besides machine-checked documentation. For instance, it could be used to eliminate the hs-boot or hi-boot files used by some compilers when dealing with recursive modules.
Why *does* ghc require hs-boot files? What can be gleaned from an hs-boot file that couldn't be expressed in the corresponding hs file? For example, why doesn't ghc simply require that at least one module in a recursive group contain an explicit export list mentioning only explicitly typed symbols? -- Ben

On Wed, Feb 22, 2006 at 12:07:44PM +0000, Malcolm Wallace wrote:
At the moment, only one type signature is permitted per entity (except for FFI foreign exports, where the exported signature may be more specific than the definitional signature). My proposal is that the normal export list can have signatures /in addition to/ the definitional signature, but that if there are thus two signatures for an entity, they must be identical. This is to prevent the case where one modifies the definition of the function, making it more general, but forgets to modify the corresponding export.
Another reason we might want to allow both is for scoped type variables. We should probably only allow type variables in the definitional signature to scope over the body of the function since it just doesn't feel right for something in the export list to scope over the body of a function in the module. John -- John Meacham - ⑆repetae.net⑆john⑈
participants (12)
-
Aaron Denney
-
Ben Rudiak-Gould
-
Cale Gibbard
-
Christopher Brown
-
Georg Martius
-
Jared Updike
-
Johannes Waldmann
-
John Meacham
-
Ketil Malde
-
Malcolm Wallace
-
Tomasz Zielonka
-
Wolfgang Jeltsch