[Haskell-cafe] Re: Status of TypeDirectedNameResolution proposal?

Ketil Malde ketil at malde.org
Sun Nov 22 14:13:02 EST 2009


Robert Greayer <robgreayer at gmail.com> writes:

>> > allow local modules.
>> >
>> > module Foo where
>> >   module Bar where
>> >     data Bar = Bar { x :: Int, y :: Int }
>> >   module Baz where
>> >     data Baz = Baz { x :: Int, y :: Int }
>> >
>> >   f a b = Bar.x a + Baz.y b

>> Independent of TDNR I would welcome this. Maybe Ticket 2551 ("Allow
>> multiple modules per source file") [1] should be reconsidered.

> Although ticket 2551 is not exactly what Luke is suggesting (which would be
> an extension to the language, whereas, if I'm not mistaken, 2551 is just a
> change to where GHC can find modules, not nesting of modules).

I think this would be great, and have very few negative
consequences.  Having multiple modules per file would make it a lot more
convenient to define tiny modules and use namespacing more actively.

E.g. if module Foo.Bar isn't found in Foo/Bar.hs GHC could look in
Foo.hs (which would just contain a concatenation of what would currently
reside in Foo.hs and Foo/Bar.hs).  So, Foo.hs could contain:

> module Foo.Bar where
>   data Bar = Bar { x :: Int, y :: Int }
>
> module Foo.Baz where
>   data Baz = Baz { x :: Int, y :: Int }
>
> module Foo where
>   import Foo.Bar as Bar
>   import Foo.Baz as Baz
> 
>   f a b = Bar.x a + Baz.y b

Since modules are already hierarchical, and there is already a mechanism
for scoping/qualification, I'm not sure modifying the language to allow
nesting actually buys anything.  Or?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants


More information about the Haskell-Cafe mailing list