
Hi all, There is currently a discussion on reddit/programming about Haskell. One complaint is that Haskell functions often use abbreviated names. I tend to agree with that. In my personal experience it generally takes more time to learn a third party Haskell library than libraries written in other languages. I am not sure why but it could be because of function names. It seems to me that Haskell's current record syntax enhances this. Take for example the new xml library, data Element = Element { elName :: QName elAttribs :: [Attr] elContent :: [Content] elLine :: Maybe Line } data Attr = Attr { attrKey :: QName attrVal :: String } data QName = QName { qName :: String qURI :: Maybe String qPrefix :: Maybe String } Personally i would prefer it to be something like data Element = Element { name :: QualifiedName attributes :: [Attribute] content :: [Content] line :: Maybe Line } data Attribute = Attribute { key :: QualifiedName value :: String } data QualifiedName = QualifiedName { name :: String uri :: Maybe String prefix :: Maybe String } but the global scope of the record field names doesn't allow that and therefore all kinds of abbreviations are inserted in front of the record field names which are hard to remember. So a better record syntax would be welcome. Perhaps the constructor could be used to limit the scope of the record field name e.g. QualifiedName.prefix? Regards, Felix

"Felix Martini"
[..]
data QualifiedName = QualifiedName { name :: String uri :: Maybe String prefix :: Maybe String }
but the global scope of the record field names doesn't allow that and therefore all kinds of abbreviations are inserted in front of the record field names which are hard to remember. So a better record syntax would be welcome. Perhaps the constructor could be used to limit the scope of the record field name e.g. QualifiedName.prefix?
/me votes for introducing
data Attribute = Attribute { Attribute.key :: QualifiedName Attribute.value :: String }
It's surely gonna be used, and iff it becomes exceedingly wide-spread, it can be made default (in 10 years or so). OTOH, I don't like the idea of having to write "Attribute" all the time, and neither want to write pages of attrKey = Attribute.key for 1000-element records (or TH to tackle standard language problems, for that matter), so there has to be some way for library users to shorten code without being masochistic, somewhat like this: A = Attribute , that is, allow definition of data constructors in usual declarations, up to some limits. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

"Achim" == Achim Schneider
writes:
Achim> OTOH, I don't like the idea of having to write "Attribute" Achim> all the time, and neither want to write pages of Achim> attrKey = Attribute.key Achim> for 1000-element records (or TH to tackle standard language Achim> problems, for that matter), so there has to be some way for Achim> library users to shorten code without being masochistic, Achim> somewhat like this: Achim> A = Attribute Nay, there's no tax on keystrokes. Code is far more often read than written. -- Colin Adams Preston Lancashire

Colin Paul Adams
"Achim" == Achim Schneider
writes: Achim> OTOH, I don't like the idea of having to write "Attribute" Achim> all the time, and neither want to write pages of
Achim> attrKey = Attribute.key
Achim> for 1000-element records (or TH to tackle standard language Achim> problems, for that matter), so there has to be some way for Achim> library users to shorten code without being masochistic, Achim> somewhat like this:
Achim> A = Attribute
Nay, there's no tax on keystrokes.
Code is far more often read than written.
Say, did you ever read Java and wondered why you have to continuously scroll to the right albeit using a 500-column terminal? Exceedingly long names are fine to organise a large library, but becomes burdensome when code only uses a subset of it... which is usually the case. _both_ in reading and writing. The longer identifiers are, the shorter information distance between two related ones tends to be, as in generateMapThatTakesAFooAndReturnsABarBydoingBaz vs. generateMapThatTakesAFuAndReturnsABarBydoingBaz compare this with locally-defined aliases mapOfFoo and mapOfFu Short notation isn't the problem, missing explanation of it is.[1] Currently, you can observe stuff like data Abst -- raction = Foo | Bar in my code. I don't mind making that a language feature for increased profit. Anyway, my code tends to get refactored more than being read or written. I want to finish typing _before_ the next idea kicks in. [1] This, as a side note, also tends to make me hate academics. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

module Element where import QName import ... data Element = Element {name :: QName, attribs :: [Attr], content :: [Content], line :: Maybe Line} module Attr where import QName import ... data Attr = Attr {key :: QName, val :: String} module QName where import ... data QName = QName {name :: String, uri :: Maybe String, prefix :: Maybe String} module Main where import qualified QName as Q import qualified Element as E ... Q.name ... E.name ... On 2 Jan 2009, at 17:20, Felix Martini wrote:
Hi all,
There is currently a discussion on reddit/programming about Haskell. One complaint is that Haskell functions often use abbreviated names. I tend to agree with that. In my personal experience it generally takes more time to learn a third party Haskell library than libraries written in other languages. I am not sure why but it could be because of function names. It seems to me that Haskell's current record syntax enhances this. Take for example the new xml library,
data Element = Element { elName :: QName elAttribs :: [Attr] elContent :: [Content] elLine :: Maybe Line }
data Attr = Attr { attrKey :: QName attrVal :: String }
data QName = QName { qName :: String qURI :: Maybe String qPrefix :: Maybe String }
Personally i would prefer it to be something like
data Element = Element { name :: QualifiedName attributes :: [Attribute] content :: [Content] line :: Maybe Line }
data Attribute = Attribute { key :: QualifiedName value :: String }
data QualifiedName = QualifiedName { name :: String uri :: Maybe String prefix :: Maybe String }
but the global scope of the record field names doesn't allow that and therefore all kinds of abbreviations are inserted in front of the record field names which are hard to remember. So a better record syntax would be welcome. Perhaps the constructor could be used to limit the scope of the record field name e.g. QualifiedName.prefix?
Regards, Felix _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Jan 2, 2009 at 9:21 PM, Miguel Mitrofanov
module Element where import QName import ... data Element = Element {name :: QName, attribs :: [Attr], content :: [Content], line :: Maybe Line}
module Attr where import QName import ... data Attr = Attr {key :: QName, val :: String}
module QName where import ... data QName = QName {name :: String, uri :: Maybe String, prefix :: Maybe String}
module Main where import qualified QName as Q import qualified Element as E ... Q.name ... E.name ...
I'm using this pattern of writing code and, so far, I find it very convenient. Yet, the code is likely to be spread across lots of files, which is not always a Good Thing. Cristiano

module Main where import qualified QName as Q import qualified Element as E ... Q.name ... E.name ...
I'm using this pattern of writing code and, so far, I find it very convenient. Yet, the code is likely to be spread across lots of files, which is not always a Good Thing.
That's a completely different matter. Personally, I think that holding each module in a separate file is not a great idea.

On Fri, 2009-01-02 at 23:48 +0300, Miguel Mitrofanov wrote:
module Main where import qualified QName as Q import qualified Element as E ... Q.name ... E.name ...
I'm using this pattern of writing code and, so far, I find it very convenient. Yet, the code is likely to be spread across lots of files, which is not always a Good Thing.
That's a completely different matter. Personally, I think that holding each module in a separate file is not a great idea.
+1 jcc

Miguel Mitrofanov schrieb:
module Element where import QName import ... data Element = Element {name :: QName, attribs :: [Attr], content :: [Content], line :: Maybe Line}
module Attr where import QName import ... data Attr = Attr {key :: QName, val :: String}
module QName where import ... data QName = QName {name :: String, uri :: Maybe String, prefix :: Maybe String}
module Main where import qualified QName as Q import qualified Element as E ... Q.name ... E.name ...
+1 for this style http://www.haskell.org/haskellwiki/Qualified_names

On Fri, 2009-01-02 at 15:20 +0100, Felix Martini wrote:
Hi all,
There is currently a discussion on reddit/programming about Haskell. One complaint is that Haskell functions often use abbreviated names. I tend to agree with that. In my personal experience it generally takes more time to learn a third party Haskell library than libraries written in other languages. I am not sure why but it could be because of function names. It seems to me that Haskell's current record syntax enhances this. Take for example the new xml library,
data Element = Element { elName :: QName elAttribs :: [Attr] elContent :: [Content] elLine :: Maybe Line }
data Attr = Attr { attrKey :: QName attrVal :: String }
data QName = QName { qName :: String qURI :: Maybe String qPrefix :: Maybe String }
Personally i would prefer it to be something like
data Element = Element { name :: QualifiedName attributes :: [Attribute] content :: [Content] line :: Maybe Line }
data Attribute = Attribute { key :: QualifiedName value :: String }
data QualifiedName = QualifiedName { name :: String uri :: Maybe String prefix :: Maybe String }
but the global scope of the record field names doesn't allow that
They are not global. They are scoped to the module just like any other function definition. So if you were to put each record in it's own module you can have Attribute.key today. No one does this though because that's rather heavy-weight. I've suggested in #haskell a few times an orthogonal language feature that will resolve this as well as providing other nice things and, being orthogonal, it keeps namespacing to namespacing mechanisms (namely modules.) The feature is simply local modules. You'd get what you want by simply writing, module Attribute where data Attribute = Attribute { key :: QualifiedName, value :: String } I haven't been able to find any semantic difficulties with this addition. There are some choices, namely what to import and export by default and some scoping issues. My choices would be to import everything in scope at the module declaration, the containing module tacitly imports everything the contained module exports, the same notation Module.name is used so a local module would shadow a top-level (hierarchical) module of the same name (though I don't expect that to be a common case.) With these conventions there would often be nominal mutual recursion between local modules at the same level. The implementation could either check to see if there is any actual mutual recursion and give an error, or, much more preferably, simply allow mutually recursive local modules as this should be much easier to handle than mutually recursive top-level modules. Some other benefits of this would be a nice way to make abstract data types, which are also underused due to the heaviness of the module system. You could write, for example, module Stack (Stack, empty, push, pop, isEmpty) where newtype Stack a = Stack [a] empty = Stack [] push x (Stack xs) = Stack (x:xs) pop (Stack (x:xs)) = Just (x, Stack xs) pop (Stack [] ) = Nothing isEmpty (Stack xs) = null xs It should be straightforward to implement this today as a pre-processor at the cost of not allowing local modules with the same qualified name as a top-level module and losing some encapsulation. The pre-processor would simply need to extract all the local module declarations and make the appropriate hierarchical modules and add the appropriate import statements. The easiest and most restrictive way to deal with mutual recursion in this case is simply have a local module only import it's ancestor modules and any modules explicitly imported. The benefit of this approach is that it doesn't require any kind of analysis, it could be done on an almost purely textual basis.
and therefore all kinds of abbreviations are inserted in front of the record field names which are hard to remember. So a better record syntax would be welcome. Perhaps the constructor could be used to limit the scope of the record field name e.g. QualifiedName.prefix?
Regards, Felix _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Derek Elkins wrote:
I haven't been able to find any semantic difficulties with this addition.
I like it too... what I run into is that there's an implicit assumption that module of name Foo.Bar.Baz *must* be found in a file Foo/Bar/Baz.[l]hs . "module Main" seems to be the only one exempted from it. GHC uses this all the time when going looking for a module's source code. (it does help make sure that for any module name in a package, there's only one version of the source-code for that module...) So I think we need to accomplish working out the kinks we may get in trying to break this assumption. -Isaac

Isaac Dupree
Derek Elkins wrote:
I haven't been able to find any semantic difficulties with this addition.
I like it too... what I run into is that there's an implicit assumption that module of name Foo.Bar.Baz *must* be found in a file Foo/Bar/Baz.[l]hs .
Ah, surely mere practicalities will not stand in the way of improving the usability of the language?
GHC uses this all the time
..unless you want a compiler, I guess. How about this: A module may be defined in a file with a name corresponding to the module name, or any dot-separated prefix of it? I.e. the file Foo/Bar.hs will define module Foo.Bar and optionally Foo.Bar.Baz as well? GHC should then be able to find it, and I believe it already has a prioritized search mechanism (presumably, the file could be named Foo.Bar.hs, too). -k -- If I haven't seen further, it is by standing in the footprints of giants

Ketil Malde wrote:
A module may be defined in a file with a name corresponding to the module name, or any dot-separated prefix of it? I.e. the file Foo/Bar.hs will define module Foo.Bar and optionally Foo.Bar.Baz as well?
GHC should then be able to find it, and I believe it already has a prioritized search mechanism (presumably, the file could be named Foo.Bar.hs, too).
I don't think GHC actually allows that (Foo.Bar.hs, ever). But your suggestion could work. 1. Try Foo/Bar/Baz.hs ; if it exists, end search (and error if it does not contain Foo.Bar.Baz, obviously as the file's top-level module). 2. Try Foo.Bar.hs ; if it exists, end search (and error if it does not contain Foo.Bar.Baz, obviously as a sub-module). 3. Try Foo.hs ; if it exists, end search (and error if it does not contain Foo.Bar.Baz, obviously as a sub-module... or possibly as a sub-sub-module?). 4. give up :-) Note though, that local modules tempt us to a couple other things too, even though they're not necessary to the proposal and would complicate it: - access-controlled modules (e.g. if other code can't import Foo.Bar.Baz) - relative-path imports / module names (e.g. if in Foo/Bar.hs we make Baz and try to import it some way with "import Baz") and as we already mentioned, it would likely involve some implicit importing of the sub-module. translating into ordinary haskell: I think my module-search mechanism makes a well-defined, deterministic way to find the right module, no complex translation necessary (except layout rule madness maybe?). Implicit importing: submodule syntax implies adding an "import The.Module.Name" line at that point in the containing file. This would suggest that submodules must be at the top, among the imports, because all imports must syntactically be at the beginning of the file -- and there's a reason for this. Bother! Even if the reason is dependency chasing, one would think same-file dependencies aren't important, but the submodules themselves can import things from other files, so those lines should need to be near the beginning anyway. so an example could be module MyData ( module MyData.Sub, -- or equivalently, D(..) transform ) where module MyData.Sub --or "module Sub" ?? that seems a bit too ad-hoc though where data D = E | F transform :: D -> D transform F = E transform E = F ~Isaac

Cafe, I was going to write about this earlier, but I'm so ill read on the record selector papers that I deleted the draft. My proposal would be for each selector name to be a special type of "phantom" type class (existing in the intermediate language only). This type class would not be accessible by the programmer and thus s/he couldn't make a polymorphic function for which specialization would be needed. In other words - in normal circumstances there is no need for dictionaries and thus no run-time difference between this method and using different record names. Example:
data IPv4Hdr = Hdr4 { src, dst :: IPv4 } data IPv6Hdr = Hdr6 { src, dst :: IPv6 }
func4 :: IPv4Hdr -> IO () func4 hdr = do let s = src hdr ...
func6 :: IPv6Hdr -> IO () func6 hdr = do let s = src hdr ...
At some intermediate stage you'd see:
class Src h s where src :: h -> s class Dst h d where dst :: h -> d
instance Src IPv4Hdr IPv4 where src (IPv4 s _) = s instance Dst IPv4Hdr IPv4 where dst (IPv4 _ d) = d -- repeat for IPv6
The only point of frustration I see is if the programmer manually makes both data types an instance of a programmer-visible type class, thus making a polymorphic function.
class IPHdr a instance IPHdr IPv4Hdr instance IPHdr IPv6Hdr
sendPing :: (IPHdr a) => a -> IO () sendPing p = networkSend (dst p) pingPayload
In this case I'd vote for specializing the function so there still
aren't any extra dictionaries, but I know that is not always optimal.
Tom
On Sat, Jan 3, 2009 at 10:08 PM, Isaac Dupree
Ketil Malde wrote:
A module may be defined in a file with a name corresponding to the module name, or any dot-separated prefix of it? I.e. the file Foo/Bar.hs will define module Foo.Bar and optionally Foo.Bar.Baz as well?
GHC should then be able to find it, and I believe it already has a prioritized search mechanism (presumably, the file could be named Foo.Bar.hs, too).
I don't think GHC actually allows that (Foo.Bar.hs, ever). But your suggestion could work.
1. Try Foo/Bar/Baz.hs ; if it exists, end search (and error if it does not contain Foo.Bar.Baz, obviously as the file's top-level module). 2. Try Foo.Bar.hs ; if it exists, end search (and error if it does not contain Foo.Bar.Baz, obviously as a sub-module). 3. Try Foo.hs ; if it exists, end search (and error if it does not contain Foo.Bar.Baz, obviously as a sub-module... or possibly as a sub-sub-module?). 4. give up :-)
Note though, that local modules tempt us to a couple other things too, even though they're not necessary to the proposal and would complicate it: - access-controlled modules (e.g. if other code can't import Foo.Bar.Baz) - relative-path imports / module names (e.g. if in Foo/Bar.hs we make Baz and try to import it some way with "import Baz")
and as we already mentioned, it would likely involve some implicit importing of the sub-module.
translating into ordinary haskell: I think my module-search mechanism makes a well-defined, deterministic way to find the right module, no complex translation necessary (except layout rule madness maybe?). Implicit importing: submodule syntax implies adding an "import The.Module.Name" line at that point in the containing file. This would suggest that submodules must be at the top, among the imports, because all imports must syntactically be at the beginning of the file -- and there's a reason for this. Bother! Even if the reason is dependency chasing, one would think same-file dependencies aren't important, but the submodules themselves can import things from other files, so those lines should need to be near the beginning anyway.
so an example could be
module MyData ( module MyData.Sub, -- or equivalently, D(..) transform ) where
module MyData.Sub --or "module Sub" ?? that seems a bit too ad-hoc though where data D = E | F
transform :: D -> D transform F = E transform E = F
~Isaac
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 4 Jan 2009, at 07:11, Thomas DuBuisson wrote:
My proposal would be for each selector name to be a special type of "phantom" type class (existing in the intermediate language only). This type class would not be accessible by the programmer and thus s/he couldn't make a polymorphic function for which specialization would be needed. In other words - in normal circumstances there is no need for dictionaries and thus no run-time difference between this method and using different record names.
Example:
data IPv4Hdr = Hdr4 { src, dst :: IPv4 } data IPv6Hdr = Hdr6 { src, dst :: IPv6 }
At some intermediate stage you'd see:
class Src h s where src :: h -> s class Dst h d where dst :: h -> d
class Src h s | h -> s

Isaac Dupree
A module may be defined in a file with a name corresponding to the module name, or any dot-separated prefix of it. I.e. the file Foo/Bar.hs will define module Foo.Bar and optionally Foo.Bar.Baz as well.
Note though, that local modules tempt us to a couple other things too, even though they're not necessary to the proposal and would complicate it:
- access-controlled modules (e.g. if other code can't import Foo.Bar.Baz)
This has been requested on and off, typically exposing internals for testing purposes.
- relative-path imports / module names (e.g. if in Foo/Bar.hs we make Baz and try to import it some way with "import Baz")
My choice would be to be cavalier about it, and sweep these under the orthogonality carpet :-) I'm not convinced they would complicate things - not a lot, at any rate. If possible the system should be designed so that sub-modules should behave just as if they were defined in files in the appropriate subdirectory. Is it possible? OTOH, a bonus would be that you might avoid the need to bootstrap recursive modules if you put them in the same file?
and as we already mentioned, it would likely involve some implicit importing of the sub-module.
I must have missed this, could you help me with a pointer?
I think my module-search mechanism makes a well-defined, deterministic way to find the right module
Yes.
Implicit importing: submodule syntax implies adding an "import The.Module.Name" line at that point in the containing file.
I'm not sure I agree with that, I don't see why we shouldn't treat these modules as ordinary modules. One of the motivations for doing this is to qualify record labels - not being able to specify "import .. qualified" or "as ..." seems like rather a loss.
This would suggest that submodules must be at the top, among the imports, because all imports must syntactically be at the beginning of the file -- and there's a reason for this.
Which is? Do we avoid one pass, or what?
so an example could be
module MyData ( module MyData.Sub, -- or equivalently, D(..) transform ) where -- so I would require this as well, import MyData.Sub (transform, D(..))
module MyData.Sub --or "module Sub" ?? that seems a bit too ad-hoc though where data D = E | F
transform :: D -> D transform F = E transform E = F
Another example: ------------------------------ module Foo where import qualified Foo.Bar as Bar import Foo.Zot f z = x z -- z = Zot.z, f :: Z -> Float g b = Bar.x b + Bar.y b ... module Foo.Bar where data B = B { x, y :: Int } ... module Foo.Zot where data Z = Z { x :: Float } ... ------------------------------ I'd make an exception for Main, which would count as no top-level module, and thus allow module Main where import ... import Sub ... module Sub where -- not Main.Sub, but possibly FileName.Sub? import ... ... -k -- If I haven't seen further, it is by standing in the footprints of giants

Ketil Malde
Implicit importing: submodule syntax implies adding an "import The.Module.Name" line at that point in the containing file.
I'm not sure I agree with that, I don't see why we shouldn't treat these modules as ordinary modules. One of the motivations for doing this is to qualify record labels - not being able to specify "import .. qualified" or "as ..." seems like rather a loss.
import [qualified] module Foo [as F] [hiding(baz)] where bar = undefined baz = bar OTOH, the Ocaml folks are going to ridicule us even more. "Now they redid the module system, and it's still second-class" -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

Achim Schneider
Implicit importing: submodule syntax implies adding an "import The.Module.Name" line at that point in the containing file.
I'm not sure I agree with that, I don't see why we shouldn't treat these modules as ordinary modules.
import [qualified] module Foo [as F] [hiding(baz)] where bar = undefined baz = bar
Why do you want the 'where' there? Why not simply treat a file Foo.Bar as a concatenation of module Foo.Bar and optionally modules Foo.Bar.*?
OTOH, the Ocaml folks are going to ridicule us even more. "Now they redid the module system, and it's still second-class"
Well, they would be wrong, wouldn't they? I don't want to "redo" the module system, and in fact, I think my proposal wouldn't change the language at all, merely how the compiler searches for modules. (Which it would be nice if the compilers agreed upon, of course.) -k -- If I haven't seen further, it is by standing in the footprints of giants

Ketil Malde
Achim Schneider
writes: import [qualified] module Foo [as F] [hiding(baz)] where bar = undefined baz = bar
Why do you want the 'where' there? Why not simply treat a file Foo.Bar as a concatenation of module Foo.Bar and optionally modules Foo.Bar.*?
Because the module definition syntax is "module Foo[(exports] where"... technically, it's not necessary, but it's nice.
OTOH, the Ocaml folks are going to ridicule us even more. "Now they redid the module system, and it's still second-class"
Well, they would be wrong, wouldn't they? I don't want to "redo" the module system, and in fact, I think my proposal wouldn't change the language at all, merely how the compiler searches for modules. (Which it would be nice if the compilers agreed upon, of course.)
It's just that inline modules, especially that syntax above, reminded me of Ocaml. It's not far from there to foo = module Foo where bar = undefined import foo -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

Achim Schneider
Ketil Malde
wrote: Achim Schneider
writes: import [qualified] module Foo [as F] [hiding(baz)] where bar = undefined baz = bar
Why do you want the 'where' there? Why not simply treat a file Foo.Bar as a concatenation of module Foo.Bar and optionally modules Foo.Bar.*?
Because the module definition syntax is "module Foo[(exports] where"... technically, it's not necessary, but it's nice.
Additionally, I don't think concatenation works well here, n-ary trees work better. module Foo where import module Bar where import module Baz where quux = undefined quux' = quux . quux quux'' = quux' . quux' quux''' = quux'' . quux'' would be nice. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

Achim Schneider
writes:
import [qualified] module Foo [as F] [hiding(baz)] where bar = undefined baz = bar
Why do you want the 'where' there?
Because the module definition syntax is "module Foo[(exports] where"... technically, it's not necessary, but it's nice.
Right - I missed the 'module' and just read it as an import statement. Clearly your proposal here goes beyond mine, what are the advantages? I.e, what's the rationale for syntactical changes instead of
simply treat[ing] a file Foo.Bar as a concatenation of module Foo.Bar and optionally modules Foo.Bar.*?
-k -- If I haven't seen further, it is by standing in the footprints of giants

Ketil Malde
Achim Schneider
writes: import [qualified] module Foo [as F] [hiding(baz)] where bar = undefined baz = bar
Why do you want the 'where' there?
Because the module definition syntax is "module Foo[(exports] where"... technically, it's not necessary, but it's nice.
Right - I missed the 'module' and just read it as an import statement. Clearly your proposal here goes beyond mine, what are the advantages? I.e, what's the rationale for syntactical changes instead of
module Foo where [...] import Foo just doesn't look elegant to my eyes so I'd like to have it in one statement, that's all. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

Derek Elkins
module Attribute where data Attribute = Attribute { key :: QualifiedName, value :: String }
+1 Assuming that the above definition is inside a file called Foo/Bar.hs and, syntactically, inside a "module Foo where", I think a sane way to search for the module Foo.Bar.Attribute is a) Foo.Bar.Attribute.hs b) Foo/Bar.Attribute.hs c) Foo/Bar/Attribute.hs d) Foo.Bar.hs:Attribute e) Foo/Bar.hs:Attribute ...I guess you see a pattern emerging. It's not entirely unlike public inner java classes[1] The reason that the Main module is an exception to the naming/placement rules is that it's _always_ the root of the search tree, which is only confusing if you insist on being confused by it[2]. Furthermore, if you import Foo.Bar , you get Attribute.(..) imported by default, _except_ if you also do import [qualified] Foo.Bar.Attribute [as A] This fixes both the insanity of having thousands of three-line modules in thousands of files (which noone wants to manage) and source directories consisting of more directories than files. [1]uhmm... can inner classes be public? I think I never tried... [2]like javac chooses to be. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.
participants (11)
-
Achim Schneider
-
Colin Paul Adams
-
Cristiano Paris
-
Derek Elkins
-
Felix Martini
-
Henning Thielemann
-
Isaac Dupree
-
Jonathan Cast
-
Ketil Malde
-
Miguel Mitrofanov
-
Thomas DuBuisson