
I suggest to add instead of (or with) export section Pragma EXPORT: We have 3 values: public, abstract and private. Data(with newtypes and types,..) could be public, like `Data(...)` or abstract `Data`. Other cases abstract = public. {-# EXPORT <smth> #-} pragma is valid till next {-# EXPORT <smth> #-}. We also can add local pragma: {-# EXPORT <smth> from #-} ... {-# EXPORT <smth> untill #-} Outside of block is rule of previous {-# EXPORT <smth> #-}. Finally we also have rule for 1: {-# EXPORT <smth> one #-} Example module C where {-# EXPORT public #-} data A1... data A2... {-# EXPORT abstract from #-} newtype A3... data A4... {-# EXPORT abstract until #-} type A5... {-# EXPORT private one #-} data A6... foo = ... {-# EXPORT private one #-} bar = ... baz = ... lorem = ... {-# EXPORT private #-} insput ... dolor = .. sit = ... {-# EXPORT public one #-} amen = ... consectetur = ... adipisicing = ... elit = ... sed = ... eiusmod = ... tempor = ... incididunt = ... {-# EXPORT public from #-} ut = ... labore = ... et = ... {-# EXPORT public until #-} dolore = ... magna = ... aliqua = ... is the same as module C ( A1(..) , A2(..) , A3 , A4 , A5(..) , foo , baz , lorem , amen , ut , labore , et ) where data A1... data A2... newtype A3... data A4... type A5... data A6... foo = ... bar = ... baz = ... lorem = ... insput ... dolor = .. sit = ... amen = ... consectetur = ... adipisicing = ... elit = ... sed = ... eiusmod = ... tempor = ... incididunt = ... ut = ... labore = ... et = ... dolore = ... magna = ... aliqua = ... We also could have complex pragma, like {-# EXPORT inherit one foo #-} bar=... Backward compatibility: module A where ... ~ module A where {-# EXPORT public #-} ... module B ( .... ) where ... ~ module B ( .... ) where {-# EXPORT private #-} ... -- View this message in context: http://haskell.1045720.n5.nabble.com/Proposal-Pragma-EXPORT-tp5736547.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Mon, Sep 16, 2013 at 4:09 PM, Wvv
I suggest to add instead of (or with) export section Pragma EXPORT:
I doubt this has much chance, since haskell already made its choice here a long time ago (and even if it were still up for discussion, PRAGMA isn't right for it), but this brings up a design question I've had. I too prefer to declare visibility on the declaration rather than in a separate list. C doesn't really have a proper module system, but header files are effectively a separate module signature. C++ and Java and go preferred to mark visibility on the declaration. The ML family keeps visibility and declarations separate, which is where I assume haskell got it (that or maybe modula?). In the case of the MLs, though, it's a much more developed concept, since they have module signatures and functors and all that. In light of haskell's very basic module system, is there any particular philosophical reason to prefer a separate export list? Or are those who prefer it for practical reasons? The only thing I can think of is that it provides a nice summary of the module, which haddock capitalizes on. But when I want a summary, I look at haddock, which would already be capable of hiding internal definitions. I have heard that haskell's module system was originally intended as a kind of simple-as-possible placeholder (like records... cough cough), maybe the designers though an ML-style module system might eventually materialize? To me it's always been a hassle to have to jump to the top of the file and fiddle with the export list, so much so that I tend to leave it off until a module is pretty stabilized. It can also be confusing when the export list is in a different order from the declarations. Sometimes I want to explicitly mark something private, and simply "doesn't happen to be in the export list" is too implicit, so I wind up putting a _ on it. None of this is a big deal, but I'm curious about other's opinions on it. Are there strengths to the separate export list that I'm missing?

On 17 September 2013 09:35, Evan Laforge
On Mon, Sep 16, 2013 at 4:09 PM, Wvv
wrote: I suggest to add instead of (or with) export section Pragma EXPORT:
I doubt this has much chance, since haskell already made its choice here a long time ago (and even if it were still up for discussion, PRAGMA isn't right for it), but this brings up a design question I've had.
I too prefer to declare visibility on the declaration rather than in a separate list. C doesn't really have a proper module system, but header files are effectively a separate module signature. C++ and Java and go preferred to mark visibility on the declaration. The ML family keeps visibility and declarations separate, which is where I assume haskell got it (that or maybe modula?). In the case of the MLs, though, it's a much more developed concept, since they have module signatures and functors and all that.
In light of haskell's very basic module system, is there any particular philosophical reason to prefer a separate export list? Or are those who prefer it for practical reasons? The only thing I can think of is that it provides a nice summary of the module, which haddock capitalizes on. But when I want a summary, I look at haddock, which would already be capable of hiding internal definitions. I have heard that haskell's module system was originally intended as a kind of simple-as-possible placeholder (like records... cough cough), maybe the designers though an ML-style module system might eventually materialize?
To me it's always been a hassle to have to jump to the top of the file and fiddle with the export list, so much so that I tend to leave it off until a module is pretty stabilized. It can also be confusing when the export list is in a different order from the declarations. Sometimes I want to explicitly mark something private, and simply "doesn't happen to be in the export list" is too implicit, so I wind up putting a _ on it.
None of this is a big deal, but I'm curious about other's opinions on it. Are there strengths to the separate export list that I'm missing?
I do like the actual "summary" aspect as you've noted, as I can at times be looking through the actual code rather than haddock documentation when exploring new code (or even trying to remember what I wrote in old code). It also makes actual definitions cleaner/shorter rather than cluttering them with extra annotations (either PRAGMAs or public/private markers), though this is not that big of a deal.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

It also makes actual definitions cleaner/shorter rather than cluttering them with extra annotations (either PRAGMAs or public/private markers), though this is not that big of a deal.
It's true, though you could get it pretty short, e.g. default private and leading ! for public. Go uses capitalization, though that's already taken for haskell.

Ivan Lazar Miljenovic
On 17 September 2013 09:35, Evan Laforge
wrote:
snip
None of this is a big deal, but I'm curious about other's opinions on it. Are there strengths to the separate export list that I'm missing?
I do like the actual "summary" aspect as you've noted, as I can at times be looking through the actual code rather than haddock documentation when exploring new code (or even trying to remember what I wrote in old code).
The summary of functionality that the export list provides is a very nice feature that I often miss in other languages. That being said, it brings up a somewhat related issue that may become increasingly problematic with the rising use of libraries such as lens: exporting members defined by Template Haskell. While we have nice sugar for exporting all accessors of a record (MyRecord(..)), we have no way to do the same for analogous TH-generated members such as lenses. Instead, we require that the user laboriously list each member of the record, taking care not to forget any. One approach would be to simply allow TH to add exports as presented in Ticket #1475 [1]. I can't help but wonder if there's another way, however. One (questionable) option would be to allow globbing patterns in export lists. Another approach might be to introduce some notion of a name list which can appear in the export list. These lists could be built up by either user declarations in the source module or in Template Haskell splices and would serve as a way to group logically related exports. This would allow uses such as (excuse the terrible syntax), module HelloWorld ( namelist MyDataLenses , namelist ArithmeticOps ) where import Control.Lens data MyData = MyData { ... } makeLenses ''MyDataLenses -- makeLenses defines a namelist called MyDataLenses namelist ArithmeticOps (add) add = ... namelist ArithmeticOps (sub) sub = ... That being said, there are a lot of reasons why we wouldn't want to introduce such a mechanism, * we'd give up the comprehensive summary that the export list currently provides * haddock headings already provides a perfectly fine means for grouping logically related exports * it's hard to envision the implementation of such a feature without the introduction of new syntax * there are arguably few uses for such a mechanism beyond exporting TH constructs * you still have the work of solving the issues presented in #1475 Anyways, just a thought. Cheers, - Ben [1] http://ghc.haskell.org/trac/ghc/ticket/1475

* Ben Gamari
Another approach might be to introduce some notion of a name list which can appear in the export list. These lists could be built up by either user declarations in the source module or in Template Haskell splices and would serve as a way to group logically related exports. This would allow uses such as (excuse the terrible syntax),
module HelloWorld ( namelist MyDataLenses , namelist ArithmeticOps ) where
import Control.Lens
data MyData = MyData { ... } makeLenses ''MyDataLenses -- makeLenses defines a namelist called MyDataLenses
namelist ArithmeticOps (add) add = ...
namelist ArithmeticOps (sub) sub = ...
Hi Ben, Isn't this subsumed by ordinary Haskell modules, barring the current compilers' limitation that modules are in 1-to-1 correspondence with files (and thus are somewhat heavy-weight)? E.g. the above could be structured as module MyDataLenses where data MyData = MyData { ... } makeLenses ''MyData module HelloWorld (module MyDataLenses, ...) where ... Roman

Roman Cheplyaka
* Ben Gamari
[2013-09-17 10:03:41-0400] Another approach might be to introduce some notion of a name list which can appear in the export list. These lists could be built up by either user declarations in the source module or in Template Haskell splices and would serve as a way to group logically related exports. This would allow uses such as (excuse the terrible syntax),
Hi Ben,
Isn't this subsumed by ordinary Haskell modules, barring the current compilers' limitation that modules are in 1-to-1 correspondence with files (and thus are somewhat heavy-weight)?
E.g. the above could be structured as
module MyDataLenses where data MyData = MyData { ... } makeLenses ''MyData
module HelloWorld (module MyDataLenses, ...) where ...
True. Unfortunately I've not seen much motion towards relaxing this limitation[1]. Cheers, - Ben [1] http://ghc.haskell.org/trac/ghc/ticket/2551

* Ben Gamari
Roman Cheplyaka
writes: * Ben Gamari
[2013-09-17 10:03:41-0400] Another approach might be to introduce some notion of a name list which can appear in the export list. These lists could be built up by either user declarations in the source module or in Template Haskell splices and would serve as a way to group logically related exports. This would allow uses such as (excuse the terrible syntax),
Hi Ben,
Isn't this subsumed by ordinary Haskell modules, barring the current compilers' limitation that modules are in 1-to-1 correspondence with files (and thus are somewhat heavy-weight)?
E.g. the above could be structured as
module MyDataLenses where data MyData = MyData { ... } makeLenses ''MyData
module HelloWorld (module MyDataLenses, ...) where ...
True. Unfortunately I've not seen much motion towards relaxing this limitation[1].
Cheers,
- Ben
I guess there simply were not many use cases for that. This may be one. At least if we are talking about changing the compiler anyway, it's better to stick with a well-understood and standardized mechanism. Roman
participants (5)
-
Ben Gamari
-
Evan Laforge
-
Ivan Lazar Miljenovic
-
Roman Cheplyaka
-
Wvv