[Haskell-cafe] Use of abbreviations in Haskell
Ketil Malde
ketil at malde.org
Mon Jan 5 06:23:21 EST 2009
Isaac Dupree <ml at isaac.cedarswampstudios.org> writes:
My proposal:
>> 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
More information about the Haskell-Cafe
mailing list