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

2009-11-24 Thread Richard O'Keefe



* For record selectors, currently written (x r), writing r.x is
exactly right


Algol 68 used 'x of r', which I always found rather readable.
COBOL has always used 'x of r' and 'x in r' with the same meaning.
BCPL uses 'f O§F r' which may I believe also be written 'f::r'.
Fortran uses 'r%x'.
Knuth's The Art of Computer Programming uses X(R).
Erlang uses 'x#type.r'.

r.x is no more exactly right than x r or x OF r or
anything else one might come up with.

Is there any need to still limit ourselves to ASCII?
Might we dare at long last to use the section sign §
and write r§x?  If any symbol is appropriate for getting
part of something, surely section is!  (If you want to
call it Select, why, § is a modified capital S.)
Best of all, § has no other uses in Haskell.  (It isn't
_quite_ as easy to type as dots are, but option 6 isn't
_that_ hard to type.)  Oh, and if you think dots are
great, why, § has a fat dot right in the middle of it.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-23 Thread Ketil Malde
Simon Peyton-Jones simo...@microsoft.com writes:

 Personally I think there are strong advantages to .:

I'm sorry, but I don't see it. Function composition is one of /the/ most
central concepts to functionaly programming.  Overloading dot further is
a terrible idea.  I don't see why using it for record field selection or
as flipped application makes sense at all - unless we change the
function composition operator (Haskell prime?).

  * For record selectors, currently written (x r), writing r.x is
  exactly right

Why?

  * For these unary operators, r.x really does mean (abstractly)
  select the x field from r

How so?

I guess I don't understand how particular (concrete) symbols can have an
exactly right or intrincic (abstract) meaning.

  * And that is the way that . is used for modules: M.x means select the x
function from module M

Granted, but I think this was a mistake, too.

  * You can think of qualified names for modules in the same way 
 Control.Monad means
pick the Monad module from the Control group.

Fair enough.

  * It culturally fits with the way . is used on OO languages

I don't think this is very convincing argument.  Some syntax is fairly
universal, like arithmetic or string quotes, but record selection isn't
among the most consistent.  Learning a new one is the least of your
worries if you're approaching Haskell from an OO direction.  And similar
syntax might lead people to expect similar semantics, something likely
to be wrong.

 What is the disadvantage?  Well, Haskell already uses . for composition.  
 But

  * . is already special.  If you write M.x you mean a qualified name, not 
 the
composition of data constructor M with function x

See above.

 I merely propose to make it even special-er!   

This would be okay if special is good, but I think special is rather the
opposite. 

Is there really no other symbol we can use?  E.g. one of # , @  ' ?

 I'll keep quiet about syntax now.

Okay, me too.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-20 Thread Simon Peyton-Jones
|* General Type Directed Name Resolution (GTDNR):
|For every function application f x in the program where f is a
|name, f is resolved based on the type of the argument x.
| 
...
| You suggest that GTDNR might not be a good idea, well why not? One
| reason is that it can potentially lead to a whole lot of guessing,
| slowing the compiler down dramatically and maybe even so much guessing
| that there are multiple whole-program resolutions (oh noes!). So how can
| we control that combinatorial exploration of alternatives? One way would
| be to restrict the places where we allow guessing. There's still
| potential room for combinatorial explosions but they're greatly reduced,
| both because we reduce the number of variables in the problem (so the
| combinatorics are smaller), and because we (generally) will have a good
| deal of non-variable context to anchor the disambiguation process and
| hopefully resolve the variables easily.

Yes.  I'm confident that GTDNR is not viable.  The TDNR proposal is carefully 
constrained to give a uni-directional information flow from the record 
field to select the function.  I don't think that the vastly more general idea 
you propose is going to work when combined with ordinary HM type inference, 
type classes, type functions, etc etc.

Of course, I could be wrong.

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-20 Thread John A. De Goes

GTDNR is what I really want anyway... whether or not it's possible. :-) 

At any given time, importing everything unqualified from every module used by a 
typical hs leads only to a handful of ambiguities. While the general case might 
be intractable, real-world cases might be trivial.

Regards,

John

On Nov 19, 2009, at 11:13 PM, wren ng thornton wrote:

 Twan van Laarhoven wrote:
 My point is that desugaring x.f to (f x) and treating some instances of 
 (f x) as (ModuleToGuess.f x) are two separate things. In the current 
 proposal these two are combined, but I see no reason to do so.
 To be a bit more concrete, I would propose:
  * General Type Directed Name Resolution (GTDNR):
  For every function application f x in the program where f is a  
  name, f is resolved based on the type of the argument x.
 Note that I am not saying that this is necessarily a good idea, it is just a 
 possible alternative to the current TDNR proposal.
 
 
 I'm not a big fan of any of the TDNR proposals I've seen (I think we still 
 haven't found the right way to do it without it being just a hack), but I can 
 give one good reason for why these two parts of the proposal are grouped 
 together.
 
 You suggest that GTDNR might not be a good idea, well why not? One reason is 
 that it can potentially lead to a whole lot of guessing, slowing the compiler 
 down dramatically and maybe even so much guessing that there are multiple 
 whole-program resolutions (oh noes!). So how can we control that 
 combinatorial exploration of alternatives? One way would be to restrict the 
 places where we allow guessing. There's still potential room for 
 combinatorial explosions but they're greatly reduced, both because we reduce 
 the number of variables in the problem (so the combinatorics are smaller), 
 and because we (generally) will have a good deal of non-variable context to 
 anchor the disambiguation process and hopefully resolve the variables easily.
 
 -- 
 Live well,
 ~wren
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-19 Thread Stephen Tetley
2009/11/18 Twan van Laarhoven twa...@gmail.com:


 The TDNR proposal really tries to do two separate things:

  1. Record syntax for function application.
    The proposal is to tread x.f or a variation thereof the same as (f x)

  2. Type directed name lookup.
    The proposal is to look up overloaded names based on the type of the
 first function argument.

 Why can't these be considered separately? Is there a good reason for not
 using TDNR in normal function applications? The only argument I can think of
 (compared to the record syntax) is that it would be a bigger change.

Hi Twan


Using the T combinator renamed to (#) for x.f was idiomatic Haskell
a decade ago, vis:

'Client-side Web Scripting with HaskellScript Erik Meijer, Daan
Leijen and James Hook
(PADL 1999)

'Modelling HTML in Haskell' Peter Thiemann (PADL 2000)

Quoting Erik Meijer et al.:

To reflect the influence of the OO style,
we will use the postfix function application
  object # method = method object
to mimic the object.method notation.

For your first point, I'd vote for adding (#) to Data.Function...

Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-19 Thread Simon Peyton-Jones
| 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 clarified.

| 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. 

Good qn.  I added a subsection Qualified imports to discuss.

| 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!

Yes, well see Record syntax.  Might be doable.

| 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.

Good point. I added a subsection Top-level disambiguation only

| So as far as records, TDNR doesn't seem too satisfactory.

I think these points are all addressable, more or less as OO languages do, as 
mentioned above.

Thanks for the suggestions

Simon

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-19 Thread Nicolas Pouillard
Excerpts from Twan van Laarhoven's message of Thu Nov 19 00:59:25 +0100 2009:
 Levi Greenspan wrote:
  What's the status of the TDNR proposal [1]? Personally I think it is a
  very good idea and I'd like to see it in Haskell'/GHC rather sooner
  than later. Working around the limitations of the current record
  system is one of my biggest pain points in Haskell and TDNR would be a
  major improvement. Thus I wonder if someone is actively working on
  this proposal?
 
 The TDNR proposal really tries to do two separate things:
 
   1. Record syntax for function application.
  The proposal is to tread x.f or a variation thereof the same as (f x)

It is more like (ModuleToGuess.f x) than (f x).

-- 
Nicolas Pouillard
http://nicolaspouillard.fr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-19 Thread Twan van Laarhoven

Nicolas Pouillard wrote:

The TDNR proposal really tries to do two separate things:

  1. Record syntax for function application.
 The proposal is to tread x.f or a variation thereof the same as (f x)


It is more like (ModuleToGuess.f x) than (f x).



My point is that desugaring x.f to (f x) and treating some instances of (f 
x) as (ModuleToGuess.f x) are two separate things. In the current proposal 
these two are combined, but I see no reason to do so.



To be a bit more concrete, I would propose:

  * General Type Directed Name Resolution (GTDNR):
  For every function application f x in the program where f is a name,
  f is resolved based on the type of the argument x.


Note that I am not saying that this is necessarily a good idea, it is just a 
possible alternative to the current TDNR proposal.




Twan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-19 Thread wren ng thornton

Twan van Laarhoven wrote:
My point is that desugaring x.f to (f x) and treating some instances 
of (f x) as (ModuleToGuess.f x) are two separate things. In the 
current proposal these two are combined, but I see no reason to do so.


To be a bit more concrete, I would propose:

  * General Type Directed Name Resolution (GTDNR):
  For every function application f x in the program where f is a 
  name, f is resolved based on the type of the argument x.


Note that I am not saying that this is necessarily a good idea, it is 
just a possible alternative to the current TDNR proposal.



I'm not a big fan of any of the TDNR proposals I've seen (I think we 
still haven't found the right way to do it without it being just a 
hack), but I can give one good reason for why these two parts of the 
proposal are grouped together.


You suggest that GTDNR might not be a good idea, well why not? One 
reason is that it can potentially lead to a whole lot of guessing, 
slowing the compiler down dramatically and maybe even so much guessing 
that there are multiple whole-program resolutions (oh noes!). So how can 
we control that combinatorial exploration of alternatives? One way would 
be to restrict the places where we allow guessing. There's still 
potential room for combinatorial explosions but they're greatly reduced, 
both because we reduce the number of variables in the problem (so the 
combinatorics are smaller), and because we (generally) will have a good 
deal of non-variable context to anchor the disambiguation process and 
hopefully resolve the variables easily.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Simon Peyton-Jones
| Simon, have you given any thought to how this interacts with type system
| extensions, in particular with GADTs and type families? The proposal relies
| on being able to find the type of a term but it's not entirely clear to me
| what that means. Here is an example:
| 
| foo :: F Int - Int
| foo :: Int - Int
| 
| bar1 :: Int - Int
| bar1 = foo
| 
| bar2 :: Int ~ F Int = Int - Int
| bar2 = foo
| 
| IIUC, bar1 is ok but bar2 isn't. Do we realy want to have such a strong
| dependency between name lookup and type inference? Can name lookup be
| specified properly without also having to specify the entire inference
| algorithm?

Yes I think it can, although you are right to point out that I said nothing 
about type inference.  One minor thing is that you've misunderstood the 
proposal a bit.  It ONLY springs into action when there's a dot.  So you'd have 
to write
bar1 x = x.foo
bar2 x = x.foo

OK so now it works rather like type functions.  Suppose, the types with which 
foo was in scope were
foo :: Int - Int
foo :: Bool - Char

Now imagine that we had a weird kind of type function

type instance TDNR_foo Int = Int - Int
type instance TDNR_foo Bool = Bool - Char

Each 'foo' gives a type instance for TDNR_foo, mapping the type of the first 
argument to the type of that foo.

So when we see (x.foo) we produce the following constraints

TDNR_foo tx ~ tx - tr

where x:tx and the result type is tr.  Then we can solve at our leisure. We 
can't make progress until we know 'tx', but when we do we can choose which foo 
is used.  Of course, there'd be some modest built-in machinery rather than a 
forest of 


Now you rightly ask what if
foo :: F Int - Int

Now under my type function analogy, we'd get
type instance TDNR_foo (F Int) = F Int - Int
and now we may be in trouble because type functions can't have a type function 
call in an argument pattern.

I hadn't thought of that.  The obvious thing to do is to *refrain* from adding 
a type instance for such a 'foo'.  But that would be a bit odd, because it 
would silently mean that some 'foo's (the ones whose first argument involved 
type functions) just didn't participate in TDNR at all.  But we can hardly emit 
a warning message for every function with a type function in the first argument!

I suppose that if you use x.foo, we could warn if any in-scope foo's have this 
property, saying you might have meant one of these, but I can't even consider 
them.  


GADTs, on the other hand, are no problem.


| Another example: suppose we have
| 
| data T a where
|   TInt  :: T Int
|   TBool :: T Bool
| 
| foo :: T Int - u
| foo :: T Bool - u
| 
| bar :: T a - u
| bar x = case x of
| TInt  - foo x
| TBool - foo x
| 
| Here, (foo x) calls different functions in the two alternatives, right? To be
| honest, that's not something I'd like to see in Haskell.

You mean x.foo and x.foo, right?  Then yes, certainly. 

Of course that's already true of type classes:

data T a where
 T1 :: Show a = T a
  T2 :: Sow a = T a

   bar :: a - T a - String
   bar x y = case y of
   T1 - show x
   T2 - show x

Then I get different show's.

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Simon Peyton-Jones
It's always tempting to spend a lot of time on syntax, but in this case it may 
be justified.  Syntactic brevity is a good part of the point of TDNR.  And I'm 
on a train which is a good time to argue about syntax.

Personally I think there are strong advantages to .:

 * For record selectors, currently written (x r), writing r.x is exactly right
 * For these unary operators, r.x really does mean (abstractly) select the x 
field from r
 * And that is the way that . is used for modules: M.x means select the x
   function from module M
 * You can think of qualified names for modules in the same way Control.Monad 
means
   pick the Monad module from the Control group.
 * It culturally fits with the way . is used on OO languages

What is the disadvantage?  Well, Haskell already uses . for composition.  But

 * . is already special.  If you write M.x you mean a qualified name, not the
   composition of data constructor M with function x

I merely propose to make it even special-er!   I'll keep quiet about syntax now.

Simon

| -Original Message-
| From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-
| boun...@haskell.org] On Behalf Of wren ng thornton
| Sent: 18 November 2009 03:07
| To: Haskell Cafe
| Subject: Re: [Haskell-cafe] Status of TypeDirectedNameResolution proposal?
| 
| Neil Brown wrote:
|  Having skimmed the page, it seems like the re-use of . is one of the
|  major difficulties of the proposal.  Would it be possible to use -?
|  It has been used for accessing members in C and C++, so it is not too
|  unusual a choice.
| 
| It's also the one that Perl went with.
| 
| 
|  It is already special in Haskell so it wouldn't break
|  anyone's code -- but do its other uses (case statements and lambdas)
|  mean that it would cause problems in the grammar if re-used for TDNR?
| 
| Given the other uses of - in Haskell, I'm hesitant to suggest it
| either. I seem to recall # is the option used by OCaml and a few other
| functional-OO languages. So far as I know -XMagicHash is the only thing
| that would conflict with that name so it seems far less invasive than .
| or -. Another option would be to use @ which is currently forbidden in
| expressions, though that might cause issues with System F/Core.
| 
| --
| Live well,
| ~wren
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Roman Leshchinskiy
On 18/11/2009, at 21:10, Simon Peyton-Jones wrote:

 Yes I think it can, although you are right to point out that I said nothing 
 about type inference.  One minor thing is that you've misunderstood the 
 proposal a bit.  It ONLY springs into action when there's a dot.  So you'd 
 have to write
   bar1 x = x.foo
   bar2 x = x.foo

Yes, that's what I meant to write, silly me. I promise to pay more attention 
next time.

 OK so now it works rather like type functions.  Suppose, the types with which 
 foo was in scope were
   foo :: Int - Int
   foo :: Bool - Char
 
 Now imagine that we had a weird kind of type function
 
   type instance TDNR_foo Int = Int - Int
   type instance TDNR_foo Bool = Bool - Char
 
 Each 'foo' gives a type instance for TDNR_foo, mapping the type of the first 
 argument to the type of that foo.

Hmm... GHC doesn't allow this:

type instance TDNR_foo () = forall a. () - a - a

IIUC this restriction is necessary to guarantee termination. Given your 
analogy, wouldn't this proposal run into similar problems?

 | Another example: suppose we have
 | 
 | data T a where
 |   TInt  :: T Int
 |   TBool :: T Bool
 | 
 | foo :: T Int - u
 | foo :: T Bool - u
 | 
 | bar :: T a - u
 | bar x = case x of
 |   TInt  - foo x
 |   TBool - foo x
 | 
 | Here, (foo x) calls different functions in the two alternatives, right? To 
 be
 | honest, that's not something I'd like to see in Haskell.
 
 You mean x.foo and x.foo, right?  Then yes, certainly. 
 
 Of course that's already true of type classes:
 
   data T a where
 T1 :: Show a = T a
 T2 :: Sow a = T a
 
   bar :: a - T a - String
   bar x y = case y of
   T1 - show x
   T2 - show x
 
 Then I get different show's.

How so? Surely you'll get the same Show instance in both cases unless you have 
conflicting instances in your program?

Roman
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Simon Peyton-Jones
|  Each 'foo' gives a type instance for TDNR_foo, mapping the type of the first
| argument to the type of that foo.
| 
| Hmm... GHC doesn't allow this:
| 
| type instance TDNR_foo () = forall a. () - a - a
| 
| IIUC this restriction is necessary to guarantee termination. Given your 
analogy,
| wouldn't this proposal run into similar problems?

Maybe so.  Of course I don't propose to *really* make a type function; just a 
new form of constraint.  I am not sure of the details.  But I'm disinclined to 
work it through unless there's a solid consensus in favour of doing something, 
and I do not yet sense such a consensus.  My nose tells me that the typing 
questions will not be a blocker.

|  Of course that's already true of type classes:
| 
|  data T a where
|  T1 :: Show a = T a
|T2 :: Show a = T a
| 
|bar :: a - T a - String
|bar x y = case y of
|T1 - show x
|T2 - show x
| 
|  Then I get different show's.
| 
| How so? Surely you'll get the same Show instance in both cases unless you have
| conflicting instances in your program?

T1 and T2 both bind a local (Show a) dictionary.  I suppose you could argue 
that they must be the same, yes.

But anyway, the original TDNR thing is perfectly well defined. It might 
occasionally be surprising.  But that doesn't stop the OO folk from loving it.

S
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Luke Palmer
You know, another solution to the records problem, which is not quite
as convenient but much simpler (and has other applications) is to
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



On Tue, Nov 17, 2009 at 5:18 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 | What's the status of the TDNR proposal [1]? Personally I think it is a
 | very good idea and I'd like to see it in Haskell'/GHC rather sooner
 | than later. Working around the limitations of the current record
 | system is one of my biggest pain points in Haskell and TDNR would be a
 | major improvement. Thus I wonder if someone is actively working on
 | this proposal?

 It's stalled.  As far as I know, there's been very little discussion about 
 it.  It's not a trivial thing to implement, and it treads on delicate 
 territory (how . is treated).  So I'd need to be convinced there was a 
 strong constituency who really wanted it before adding it.

 I've added an informal straw poll to the bottom of [1] to allow you to 
 express an opinion.

 Also I'm not very happy with the stacking operations part, and I'd like a 
 better idea.

 Simon


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Evan Laforge
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.


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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Edward Kmett
On Wed, Nov 18, 2009 at 3:53 PM, Evan Laforge qdun...@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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread David Menendez
On Wed, Nov 18, 2009 at 4:12 PM, Edward Kmett ekm...@gmail.com wrote:

 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.

Try Quaffle without the qualifications.

 module Quaffle where
 import qualified Bar
 import qualified Baz

 instance Bar.Foo Int where
   foo = 1

 instance Baz.Quux Int where
   foo = 2


-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Edward Kmett
Thanks! Learn something new every day. =)

-Edward Kmett

On Wed, Nov 18, 2009 at 4:29 PM, David Menendez d...@zednenem.com wrote:

 On Wed, Nov 18, 2009 at 4:12 PM, Edward Kmett ekm...@gmail.com wrote:
 
  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.

 Try Quaffle without the qualifications.

  module Quaffle where
  import qualified Bar
  import qualified Baz
 
  instance Bar.Foo Int where
foo = 1
 
  instance Baz.Quux Int where
foo = 2


 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/ http://www.eyrie.org/%7Ezednenem/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-18 Thread Twan van Laarhoven

Levi Greenspan wrote:

What's the status of the TDNR proposal [1]? Personally I think it is a
very good idea and I'd like to see it in Haskell'/GHC rather sooner
than later. Working around the limitations of the current record
system is one of my biggest pain points in Haskell and TDNR would be a
major improvement. Thus I wonder if someone is actively working on
this proposal?


The TDNR proposal really tries to do two separate things:

 1. Record syntax for function application.
The proposal is to tread x.f or a variation thereof the same as (f x)

 2. Type directed name lookup.
The proposal is to look up overloaded names based on the type of the first 
function argument.


Why can't these be considered separately? Is there a good reason for not using 
TDNR in normal function applications? The only argument I can think of (compared 
to the record syntax) is that it would be a bigger change.



Twan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Simon Peyton-Jones
| What's the status of the TDNR proposal [1]? Personally I think it is a
| very good idea and I'd like to see it in Haskell'/GHC rather sooner
| than later. Working around the limitations of the current record
| system is one of my biggest pain points in Haskell and TDNR would be a
| major improvement. Thus I wonder if someone is actively working on
| this proposal?

It's stalled.  As far as I know, there's been very little discussion about it.  
It's not a trivial thing to implement, and it treads on delicate territory (how 
. is treated).  So I'd need to be convinced there was a strong constituency 
who really wanted it before adding it.

I've added an informal straw poll to the bottom of [1] to allow you to express 
an opinion.

Also I'm not very happy with the stacking operations part, and I'd like a 
better idea.

Simon

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Matthijs Kooijman
 I've added an informal straw poll to the bottom of [1] to allow you to 
 express an opinion.

[1]: ?


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Neil Brown

Simon Peyton-Jones wrote:
| What's the status of the TDNR proposal [1]? 

It's stalled.  As far as I know, there's been very little discussion about it.  It's not a trivial thing to implement, and it treads on delicate territory (how . is treated).  
Having skimmed the page, it seems like the re-use of . is one of the 
major difficulties of the proposal.  Would it be possible to use -?  
It has been used for accessing members in C and C++, so it is not too 
unusual a choice.  It is already special in Haskell so it wouldn't break 
anyone's code -- but do its other uses (case statements and lambdas) 
mean that it would cause problems in the grammar if re-used for TDNR?


Neil.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Levi Greenspan
On Tue, Nov 17, 2009 at 1:18 PM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 | What's the status of the TDNR proposal [1]? Personally I think it is a
 | very good idea and I'd like to see it in Haskell'/GHC rather sooner
 | than later. Working around the limitations of the current record
 | system is one of my biggest pain points in Haskell and TDNR would be a
 | major improvement. Thus I wonder if someone is actively working on
 | this proposal?

 It's stalled.  As far as I know, there's been very little discussion about 
 it.  It's not a trivial thing to implement, and it treads on delicate 
 territory (how . is treated).  So I'd need to be convinced there was a 
 strong constituency who really wanted it before adding it.

Well, implementing certain protocols (e.g. based on JSON, like Bayeux
[1]) in a type-safe way requires lots of records and many of these
records have similar selectors, e.g. channel. Currently one can only
have a nice interface to such a protocol by using type classes and
creating lots of instance declarations, which is a lot of boilerplate
to be written. This would be much easier with TDNR, than with
module-scoped record selectors. Also the hack to use different modules
is further complicated by the fact that at least GHC insists on having
each module in a separate file.

As pointed out by others one may choose a different string instead of
. like -  if this makes the implementation of TDNR feasible. But
some mechanism to have some sort of scoped record selectors or TDNR is
needed in my opinion.

Many thanks,
Levi


[1] http://svn.cometd.org/trunk/bayeux/bayeux.html


 I've added an informal straw poll to the bottom of [1] to allow you to 
 express an opinion.

 Also I'm not very happy with the stacking operations part, and I'd like a 
 better idea.

 Simon


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Levi Greenspan
On Tue, Nov 17, 2009 at 1:18 PM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 I've added an informal straw poll to the bottom of [1] to allow you to 
 express an opinion.

Forgive my ignorance, but I can not find a way to edit the wiki page.
What am I doing wrong?

Cheers,
Levi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Daniel Fischer
Am Dienstag 17 November 2009 15:36:52 schrieb Levi Greenspan:
 As pointed out by others one may choose a different string instead of
 . like -  if this makes the implementation of TDNR feasible.

Or, if both of these strings would make the implementation awkward, one can 
choose a 
different but similar, ~, -- (to annoy bad syntax highlighters 8-)), 
which is 
neither special in Haskell syntax nor a prominent operator from a library.
I wouldn't lay much stress on using the same notation as other languages. After 
all, we 
have (/=) instead of (!=) and it works.

 But some mechanism to have some sort of scoped record selectors or TDNR is
 needed in my opinion.

I haven't needed the feature yet, but I think it would be A Good Thing™ to have 
it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Luke Palmer
On Tue, Nov 17, 2009 at 5:18 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 | What's the status of the TDNR proposal [1]? Personally I think it is a
 | very good idea and I'd like to see it in Haskell'/GHC rather sooner
 | than later. Working around the limitations of the current record
 | system is one of my biggest pain points in Haskell and TDNR would be a
 | major improvement. Thus I wonder if someone is actively working on
 | this proposal?

 It's stalled.  As far as I know, there's been very little discussion about 
 it.  It's not a trivial thing to implement, and it treads on delicate 
 territory (how . is treated).  So I'd need to be convinced there was a 
 strong constituency who really wanted it before adding it.

 I've added an informal straw poll to the bottom of [1] to allow you to 
 express an opinion.

And how I love expressing my opinion :-P.   I would if only I could
figure out how to edit the page!  Am I being dense?  (Yes, I am logged
in)

Luke

 Also I'm not very happy with the stacking operations part, and I'd like a 
 better idea.

 Simon


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Simon Peyton-Jones
Sigh.  Apologies.  Turns out that [1] is not publicly editable. So I've created 
a HaskellWiki page [2] and cross-linked them.

[2] http://haskell.org/haskellwiki/TypeDirectedNameResolution

You should be able to edit that!

Simon

| -Original Message-
| From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On
| Behalf Of Luke Palmer
| Sent: 17 November 2009 17:08
| To: Simon Peyton-Jones
| Cc: Levi Greenspan; Haskell Cafe
| Subject: Re: [Haskell-cafe] Status of TypeDirectedNameResolution proposal?
| 
| On Tue, Nov 17, 2009 at 5:18 AM, Simon Peyton-Jones
| simo...@microsoft.com wrote:
|  | What's the status of the TDNR proposal [1]? Personally I think it is a
|  | very good idea and I'd like to see it in Haskell'/GHC rather sooner
|  | than later. Working around the limitations of the current record
|  | system is one of my biggest pain points in Haskell and TDNR would be a
|  | major improvement. Thus I wonder if someone is actively working on
|  | this proposal?
| 
|  It's stalled.  As far as I know, there's been very little discussion about 
it.
|  It's not a trivial thing to implement, and it treads on delicate territory 
(how .
| is treated).  So I'd need to be convinced there was a strong constituency who 
really
| wanted it before adding it.
| 
|  I've added an informal straw poll to the bottom of [1] to allow you to 
express an
| opinion.
| 
| And how I love expressing my opinion :-P.   I would if only I could
| figure out how to edit the page!  Am I being dense?  (Yes, I am logged
| in)
| 
| Luke
| 
|  Also I'm not very happy with the stacking operations part, and I'd like a 
better
| idea.
| 
|  Simon
| 
| 
|  ___
|  Haskell-Cafe mailing list
|  Haskell-Cafe@haskell.org
|  http://www.haskell.org/mailman/listinfo/haskell-cafe
| 
| 
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread wren ng thornton

Neil Brown wrote:
Having skimmed the page, it seems like the re-use of . is one of the 
major difficulties of the proposal.  Would it be possible to use -?  
It has been used for accessing members in C and C++, so it is not too 
unusual a choice.


It's also the one that Perl went with.


It is already special in Haskell so it wouldn't break 
anyone's code -- but do its other uses (case statements and lambdas) 
mean that it would cause problems in the grammar if re-used for TDNR?


Given the other uses of - in Haskell, I'm hesitant to suggest it 
either. I seem to recall # is the option used by OCaml and a few other 
functional-OO languages. So far as I know -XMagicHash is the only thing 
that would conflict with that name so it seems far less invasive than . 
or -. Another option would be to use @ which is currently forbidden in 
expressions, though that might cause issues with System F/Core.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-17 Thread Roman Leshchinskiy
Simon, have you given any thought to how this interacts with type system 
extensions, in particular with GADTs and type families? The proposal relies on 
being able to find the type of a term but it's not entirely clear to me what 
that means. Here is an example:

foo :: F Int - Int
foo :: Int - Int

bar1 :: Int - Int
bar1 = foo

bar2 :: Int ~ F Int = Int - Int
bar2 = foo

IIUC, bar1 is ok but bar2 isn't. Do we realy want to have such a strong 
dependency between name lookup and type inference? Can name lookup be specified 
properly without also having to specify the entire inference algorithm?

Another example: suppose we have

data T a where
  TInt  :: T Int
  TBool :: T Bool

foo :: T Int - u
foo :: T Bool - u

bar :: T a - u
bar x = case x of
  TInt  - foo x
  TBool - foo x

Here, (foo x) calls different functions in the two alternatives, right? To be 
honest, that's not something I'd like to see in Haskell.

Roman


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe