[Haskell-cafe] Status of TypeDirectedNameResolution proposal?

Edward Kmett ekmett at gmail.com
Wed Nov 18 16:12:34 EST 2009


On Wed, Nov 18, 2009 at 3:53 PM, Evan Laforge <qdunkan at gmail.com> wrote:

> The proposal has this sentence, apparently in reference to using
> qualified imports: "This is sufficient, but it is just sufficiently
> inconvenient that people don't use it much."  Does this mean qualified
> imports?  I use them exclusively, and I'd love it if everyone else
> used them too.
>

A possibly irrelevant aside:

Qualified imports are some times problematic when you need to work with
classes from the module. You can't define a member of two instances from
different two modules that define classes with conflicting member names.
This can lead to situations where you have no option but to have orphan
instances.

module Bar where
class Foo a where
   foo :: a

module Baz where
class Quux a where
  foo :: a

module Quaffle where
import qualified Bar
import qualified Baz

instance Bar.Foo Int where
  Bar.foo = 1
-- ^- syntax error.

instance Baz.Quux Int where
  Baz.foo = 2

I suppose this could possibly be fixed if something deep in the parser
allowed a QName there.

-Edward Kmett


> Anyway, a few concerns about TDNR as prosposed:
>
> One thing I'd really like that this would provide is shorter record
> selection.  "b.color" is a lot nicer than "Button.btn_color b".  Or
> would it?  It seems like under a TDNR scheme to be able to write
> "b.color" I'd have to either import "color" explicitly or go over to
> the unqualified import world.  I don't really want to do the latter,
> but I also wouldn't want to maintain explicit import lists.  Also, as
> far as I can see this doesn't provide is nice record update syntax.
> If I can write "b.color" I want to be able to write "b2 = b.color :=
> red"!
>
> I think this will also lead to either lots of name shadowing warnings
> or more trouble picking variable names.  The short perspicuous names
> this allows are also the most convenient for local variables.  I don't
> want to suddenly not be able to use a 'color' variable name because
> some record has a 'color' field.  A record system (and OO languages)
> would have no trouble with 'let color = b.color' but as far as I can
> see TDNR would have a problem.
>
> So as far as records, TDNR doesn't seem too satisfactory.
>
> I'm also worried about the use of dot with regards to a possible
> future record system.  If we're already using dot for TDNR it's seems
> like it would be even harder for a record system to use it.  I'm not
> saying this very well, but it seems like both proposals solve
> overlapping problems:  TDNR provides convenient "method" calls and
> convenient field access as a side-effect, a record system would
> provide convenient field access and some form of subtyping.  I think
> records are more interesting and I worry that TDNR would lessen
> motivation to implement records or make them more tricky to implement.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091118/7675436b/attachment.html


More information about the Haskell-Cafe mailing list