Re: ORF for fields of higher-ranked type [was: TDNR without new operators or syntax changes]

2016-06-22 Thread Adam Gundry
On 15/06/16 04:29, AntC wrote:
> ...
>
> The earlier design for SORF tried to support higher-ranked fields.
> https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/SORF
> 
> That had to be abandoned,
> until explicit type application was available IIRC.
> 
> We now have type application in GHC 8.0.
> 
> Is there some hope for higher-rank type fields?

Unfortunately, doing ORF with higher-rank fields is a bit of a
non-starter, even with explicit type application, because the
combination would break bidirectional type inference and require
impredicativity. This was part of the reason we ended up preferring an
explicit syntactic marker for ORF-style overloaded labels.

For example, consider this (rather artificial) type:

data T = MkT { foo :: ((forall a . a -> a) -> Bool) -> Bool }
-- foo :: T -> ((forall a . a -> a) -> Bool) -> Bool

Suppose `t :: T`. When type-checking `foo t (\ k -> k k True)`, the
compiler will infer (look up) the type of `foo` and use it to check the
types of the arguments. The second argument type-checks only because we
are "pushing in" the type `(forall a . a -> a) -> Bool` and hence we
know that the type of `k` will be `forall a . a -> a`.

Now suppose we want to type-check `#foo t (\ k -> k k True)` using ORF
instead. That ends up deferring a constraint `HasField r "foo" a` to the
constraint solver, and inferring a type `a` for `#foo t`, so we can't
type-check the second argument. Only the constraint solver will figure
out that `a` should be impredicatively instantiated with a polytype. We
end up needing to do type inference in the presence of impredicativity,
which is a Hard Problem.

There is some work aimed at improving GHC's type inference for
impredicativity, so perhaps there's hope for this in the future.
Explicit type application makes it possible (in principle, modulo
#11352) for the user to write something like

#foo @T @(((forall a . a -> a) -> Bool) -> Bool) t (\ k -> k k True)

although they might not want to! But the ramifications haven't been
fully thought through, e.g. we'd need to be able to solve the constraint

HasField T "foo" (((forall a . a -> a) -> Bool) -> Bool)

even though it has a polytype as an argument.

Sorry to be the bearer of bad news,

Adam


-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


ORF for fields of higher-ranked type [was: TDNR without new operators or syntax changes]

2016-06-14 Thread AntC
> Adam Gundry writes:
> ... Having spent more time thinking about record field overloading
>  than perhaps I should, ...

Thanks Adam, another thing on the back burner ...

The earlier design for SORF tried to support higher-ranked fields.
https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/SORF

That had to be abandoned,
until explicit type application was available IIRC.

We now have type application in GHC 8.0.

Is there some hope for higher-rank type fields?

AntC



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-29 Thread Peter
AntC wrote
> I'm not seeing you're proposing anything that's significantly different
> to DuplicateRecordFields. That has the advantage we can use it now.
> 
> If you are proposing something different, you need to explain
> in a lot more detail, so that we can see the advantages.
> 
> So [ref Evan] even though a field name is a first-class function usually,
> DuplicateRecordFields only gets triggered where you use the bare name.
> 
> [Ref Peter] I'm not seeing why you're talking about two passes,
> but that does not sound like a robust approach.
> (Can you be sure two passes is enough?
>  If it is enough, why can't the second pass's logic
>  get built into the first?)

DRF only works for records, but brings polymorphism, duplicate definitions
in the same module, and other goodies. This proposal will work for any
function, but only helps with disambiguation. There is some overlap, but it
is a different solution for different requirements.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/TDNR-without-new-operators-or-syntax-changes-tp5835927p5836818.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-28 Thread AntC
> Evan Laforge  gmail.com> writes:
>
> That's why I was trying to emphasize "not an operator". 
> TDNR is complicated because ...

>> Peter voldermort writes:
>> A slightly more refined definition for disambiguation: ...

Hi Evan, Peter, (and even James),

I'm not seeing you're proposing anything that's significantly different
to DuplicateRecordFields. That has the advantage we can use it now.

If you are proposing something different, you need to explain
in a lot more detail, so that we can see the advantages.

So [ref Evan] even though a field name is a first-class function usually,
DuplicateRecordFields only gets triggered where you use the bare name.

[Ref Peter] I'm not seeing why you're talking about two passes,
but that does not sound like a robust approach.
(Can you be sure two passes is enough?
 If it is enough, why can't the second pass's logic
 get built into the first?)

Yes DuplicateRecordFIelds is a bit of a hack.
The proper solution (MagicTypeClasses) is still awaited.

Can you explain why GHC should depart from that plan?


AntC

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-28 Thread Evan Laforge
On Sat, May 28, 2016 at 3:13 AM, AntC  wrote:
>> Evan Laforge  gmail.com> writes:
>
>> ... what would happen if you tried to do records
>> just like C structs?  So e.g. a•b requires 'a' to be a record with a
>> 'b' field, and is just one identifier, no functions involved, and 'b'
>> is not a separate value.
>
> Hi Evan, um, that's the original TDNR isn't it?
> http://hackage.haskell.org/trac/haskell-prime/wiki/
> TypeDirectedNameResolution
> As per Jeremy's ref in the first post in this thread.
>
> If you're talking C then that blobby thing between a and b
> should be a dot(?) as postfix operator.
> And it is an operator, not "just one identifier".

That's why I was trying to emphasize "not an operator".  TDNR is
complicated is because the field name is a first class value, so it's
a function applied to a record, and now we have to disambiguate the
function.  I didn't meant that.

I guess C (and Java and all the others) does call "." an operator
because it parses as one and has precedence, but it works with
identifiers, not values, and has special grammar.  It's not an
operator from the haskell point of view.  The C compiler isn't doing
any overloading or disambiguation.  As far as I understand it the
implementation is straightforward.  Could ghc do something similarly
straightforward?  It already does for qualified module names, and in
the same way in M.a, ".a" is not a function that gets something out of
an M.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-28 Thread Peter
A slightly more refined definition for disambiguation:

1) If a type signature has been supplied for an ambiguous name, GHC will
attempt to disambiguate with the type signature alone.
2) If the name is a function applied to an explicit argument, and the type
of the argument can be inferred without disambiguating anything (or is
supplied as a type signature), then GCH will attempt to disambiguate by
matching the type of the argument.

This is sufficient to cover all of the motivating examples proposed for
TDNR, and every case where I have personally wanted it. It does not require
backtracing (although it may require two passes to disambiguate on the
inferred type of an argument), and disambiguating one name will not depend
on disambiguating any other name.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/TDNR-without-new-operators-or-syntax-changes-tp5835927p5836791.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-28 Thread AntC
> Evan Laforge  gmail.com> writes:

> ... what would happen if you tried to do records
> just like C structs?  So e.g. a•b requires 'a' to be a record with a
> 'b' field, and is just one identifier, no functions involved, and 'b'
> is not a separate value.

Hi Evan, um, that's the original TDNR isn't it?
http://hackage.haskell.org/trac/haskell-prime/wiki/
TypeDirectedNameResolution
As per Jeremy's ref in the first post in this thread.

If you're talking C then that blobby thing between a and b
should be a dot(?) as postfix operator.
And it is an operator, not "just one identifier".

Then if you intend that dot bind tighter than function apply,
but not as tight as Module name prefixes,
you have the original TDNR.

If you intend some operator symbol other than dot,
there's a risk existing code is already using it,
and/or it's not ASCII.
And you're introducing an operator with very non-standard binding rules.
(The reason SPJ chose dot, apart from that following other languages,
 is there's already a precedent for it being tight-binding in Module prefixes.)

> 
> I didn't see that option on the increasingly all-encompassing
> Records wiki page.
> 

It's linked as Solution 2 on that records page, called "TDNR".

Surely there can't be any records approaches that haven't been aired by now?
And GHC's direction is set.


AntC
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-28 Thread Evan Laforge
As long as were back on this topic again (sort of), and just to
satisfy my curiousity, what would happen if you tried to do records
just like C structs?  So e.g. a•b requires 'a' to be a record with a
'b' field, and is just one identifier, no functions involved, and 'b'
is not a separate value.

I could see how people might think it was not powerful enough or not
very idiomatic, but is there something about haskell that would make
it just not work?

I didn't see that option on the increasingly all-encompassing Records wiki page.

On Fri, May 27, 2016 at 10:33 PM, AntC  wrote:
>> Dan Doel  gmail.com> writes:
>>
>>> On Thu, May 26, 2016 at 5:14 AM, Peter  hotmail.com> wrote:
>>> Solving for everything but f, we get f :: T -> Int.
>>
>> So TDNR happens for things in function position (applied to something).
>
> Before we get carried away, TDNR doesn't happen at all.
> You're speculating about what might be able to happen?
>
>> > Solving for everything but f, we get f :: T -> Int.
>>
>> So TDNR happens for things in argument position.
>
> [By "things" there you mean functions.]
>
> TDNR as originally spec'd wouldn't try to solve this.
> (Because there's no dot-postfix invocation.)
> And my reading of DuplicateRecordFields is that won't either.
>
> There's a good reason. We're trying to solve for record field accessors.
> So unlike Dan's examples, there's a bunch of same-named functions:
> personId :: T -> Int
> personId :: U -> Int
> personId :: V -> Int
>
> personId's are always Ints. There's no point trying to work 'outside in',
> because it won't disambiguate anythng.
>
>> > May not be solvable, would fail to disambiguate.
>>
>> But there's exactly one combination of f and v definitions that will
>> succeed with the right type. So why doesn't that happen?
>
> Because in general you have to run the whole of type inference
> to solve this case.
> (That's Peter's step 2. in his earlier message.)
> But we can't run type inference until we've disambiguated all names.
> Chicken and egg.
>
>> ... Another way to phrase the question is: why would
>> TDNR only disambiguate based on argument types of functions
>> and not on return types? ...
>
> Because, per above, the return types are all the same
> (for same-named field accessors).
>
>> ... Is it doing backtracking search?
>> How do you add backtracking search to GHC's inference algorithm? Etc.
>
> No GHC does not now do backtracking search.
> No it couldn't be somehow bolted on.
> There's no guarantee that adding backtracking
> could resolve any more cases that can be solved now,
> because now we have hugely powerful inference honed for decades,
> and type system design to exploit it.
>
>> ... And type classes fix that by
>> turning overloading into something that happens via an agreed upon
>> interface, with declared conventions, and which can be abstracted over
>> well. ...
>
> Yes, so the full program for ORF is to make 'Magic Type Classes'
> seem to the type inferencer like regular class-based overloading.
>
>> But also, for something as far reaching as doing TDNR for every
>> ambiguous name, it's not terribly clear to me what a good algorithm
>> even is, unless it's only good enough to handle really simple
>> examples, and just doesn't work most of the time ...
>
> DuplicateRecordFields is aiming for the simple examples.
> If some case isn't simple enough,
> you can always add signatures until it is.
>
>
> AntC
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-27 Thread AntC
> Dan Doel  gmail.com> writes:
> 
>> On Thu, May 26, 2016 at 5:14 AM, Peter  hotmail.com> wrote:
>> Solving for everything but f, we get f :: T -> Int.
> 
> So TDNR happens for things in function position (applied to something).

Before we get carried away, TDNR doesn't happen at all.
You're speculating about what might be able to happen?
 
> > Solving for everything but f, we get f :: T -> Int.
> 
> So TDNR happens for things in argument position.

[By "things" there you mean functions.]

TDNR as originally spec'd wouldn't try to solve this.
(Because there's no dot-postfix invocation.)
And my reading of DuplicateRecordFields is that won't either.

There's a good reason. We're trying to solve for record field accessors.
So unlike Dan's examples, there's a bunch of same-named functions:
personId :: T -> Int
personId :: U -> Int
personId :: V -> Int

personId's are always Ints. There's no point trying to work 'outside in',
because it won't disambiguate anythng.

> > May not be solvable, would fail to disambiguate.
> 
> But there's exactly one combination of f and v definitions that will
> succeed with the right type. So why doesn't that happen?

Because in general you have to run the whole of type inference
to solve this case.
(That's Peter's step 2. in his earlier message.)
But we can't run type inference until we've disambiguated all names.
Chicken and egg.

> ... Another way to phrase the question is: why would
> TDNR only disambiguate based on argument types of functions
> and not on return types? ...

Because, per above, the return types are all the same
(for same-named field accessors).

> ... Is it doing backtracking search?
> How do you add backtracking search to GHC's inference algorithm? Etc.

No GHC does not now do backtracking search.
No it couldn't be somehow bolted on.
There's no guarantee that adding backtracking
could resolve any more cases that can be solved now,
because now we have hugely powerful inference honed for decades,
and type system design to exploit it.

> ... And type classes fix that by
> turning overloading into something that happens via an agreed upon
> interface, with declared conventions, and which can be abstracted over
> well. ...

Yes, so the full program for ORF is to make 'Magic Type Classes'
seem to the type inferencer like regular class-based overloading.

> But also, for something as far reaching as doing TDNR for every
> ambiguous name, it's not terribly clear to me what a good algorithm
> even is, unless it's only good enough to handle really simple
> examples, and just doesn't work most of the time ...

DuplicateRecordFields is aiming for the simple examples.
If some case isn't simple enough,
you can always add signatures until it is.


AntC

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-26 Thread Dan Doel
On Thu, May 26, 2016 at 5:14 AM, Peter  wrote:
> Solving for everything but f, we get f :: T -> Int.

So TDNR happens for things in function position (applied to something).

> Solving for everything but f, we get f :: T -> Int.

So TDNR happens for things in argument position.

> May not be solvable, would fail to disambiguate.

But there's exactly one combination of f and v definitions that will
succeed with the right type. So why doesn't that happen? Here's an
intermediate step:

i1' x = f x :: Int

What happens there? Another way to phrase the question is: why would
TDNR only disambiguate based on argument types of functions and not on
return types? Why would function types even be a factor at all?

And to be honest, I don't really think the description of what the
type checker would be doing is detailed enough. If there are two
ambiguous candidates how does type checking proceed with 'the type in
the declared signature' when there are two possible signatures which
may be completely different? Is it doing backtracking search? How do
you add backtracking search to GHC's inference algorithm? Etc. The
later examples are designed to raise questions about this, too.

I'm rather of the opinion that TDNR just isn't a good feature for most
things. Implicit in the famous "How to Make Ad-hoc Polymorphism Less
Ad-hoc" is that being ad-hoc is bad. And type classes fix that by
turning overloading into something that happens via an agreed upon
interface, with declared conventions, and which can be abstracted over
well. But TDNR has none of that, so to my mind, it's not really
desirable, except possibly in cases where there is no hope of being
abstract (for instance, Agda does some TDNR for constructors in
patterns, and there isn't much basis in the underlying theory for
trying to abstract over doing induction on completely different types
with similarly named pieces; so it's more acceptable).

But also, for something as far reaching as doing TDNR for every
ambiguous name, it's not terribly clear to me what a good algorithm
even is, unless it's only good enough to handle really simple
examples, and just doesn't work most of the time (and even then, I'm
not sure it's been thought through enough to say that it's a simple
addition to GHC's type checking).

-- Dan
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-26 Thread Peter
Thank you for feeding my thoughts. How would this do for a slightly more
detailed definition?

1. If the compiler encounters an ambiguous function, it will temporarily
give it the type a -> b, or the type declared in the signature if there is
one.
2. Type inference completes as normal.
3. If the inferred or declared type for an ambiguous name is sufficient to
disambiguate it, it will be bound to the correct definition.


Dan Doel wrote
> f :: T -> Int
> f t = ...
> 
> f :: U -> Int -> Char
> f u = ...
> 
> t :: T
> t = ...
> 
> u :: U
> u = ...
> 
> i1 :: Int
> i1 = f t

Solving for everything but f, we get f :: T -> Int.


> g :: (T -> Int) -> Int
> g h = h t
> 
> i2 :: Int
> i2 = g f

Solving for everything but f, we get f :: T -> Int.


> v :: T
> v = t
> 
> v :: U
> v = u
> 
> i3 :: Int
> i3 = f v

May not be solvable, would fail to disambiguate.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/TDNR-without-new-operators-or-syntax-changes-tp5835927p5836657.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-25 Thread Dan Doel
As a supplement, here's a series of definitions to think about. The
question is: what should happen in each section, and why? The more
detailed the answer, the better. Definitions from previous sections
are in scope in subsequent ones, for convenience. The examples are
arranged in a slippery slope, but there may be more good, confusing
examples that I missed.

--- cut ---

-- 1 --

f :: T -> Int
f t = ...

f :: U -> Int -> Char
f u = ...

t :: T
t = ...

u :: U
u = ...

i1 :: Int
i1 = f t

-- 2 --

g :: (T -> Int) -> Int
g h = h t

i2 :: Int
i2 = g f

-- 3 --

v :: T
v = t

v :: U
v = u

i3 :: Int
i3 = f v

-- 4 --

class C a where
  c :: a -> Int

instance C T where
  c = f

i4 :: Int
i4 = c v

-- 5 --

main = print $ f v

--- cut ---

-- Dan

On Tue, May 24, 2016 at 4:07 AM, Adam Gundry  wrote:
> Thanks for starting this discussion! Having spent more time thinking
> about record field overloading than perhaps I should, here are some
> things to think about...
>
>
> On 22/05/16 16:01, Jeremy wrote:
>> Bertram Felgenhauer-2 wrote
 1. If the compiler encounters a term f a, and there is more than one
 definition for f in scope (after following all of the usual rules for
 qualified imports);

 2. And exactly one of these definitions matches the type of a (or the
 expected type of f if given);

 3. Then this is the definition to use.
>>>
>>> I now find that Anthony's concerns are justified. The question is, what
>>> exactly does the type matching in step 2 involve? If it is a recursive
>>> call to the type-checker then you'll have a huge performance problem.
>>
>> I was concerned about this, but not knowing anything about how
>> type-checking/inference is implemented, I wouldn't know if this is actually
>> a problem or not.
>
> Unfortunately this is indeed a problem. When the type-checker encounters
> `f a`, it infers the type of `f`, ensures it is a function type `s ->
> t`, then checks that `a` has type `s`. But if there are multiple
> possible `f`s in scope, what should it do? Options include:
>
>  1. run the entire type-checking process for each possible type of `f`
> (this is almost certainly too slow);
>
>  2. give ad-hoc rules to look at type information from the context or
> the inferred type of the argument `a`;
>
>  3. introduce a name resolution constraint and defer it to the
> constraint solver (the same way that solving for typeclasses works);
>
>  4. require a type signature in a fixed location.
>
> Both 2 and 3 would need careful specification, as they run the risk of
> exposing the type-checking algorithm to the user, and changing the
> typing rules depending on what is in scope may be problematic. In
> particular, if `f` has a higher-rank type than bidirectional type
> inference is likely to break down.
>
> The DuplicateRecordFields approach is to make use of bidirectional type
> inference (a bit like 2, but without looking at the type of the
> argument) and otherwise require a type signature. This is carefully
> crafted to avoid needing to change existing typing rules. The wiki page
> [1] sets out some of the cases in which this does and doesn't work.
>
> Point 3 is rather like the magic classes in the OverloadedRecordFields
> proposal [2] (this isn't in GHC HEAD yet, but an early version is on
> Phab [3]).
>
>
>>> If, on the other hand, you only take into account what is known about
>>> the type of a at a given time, then you need special treatment for
>>> unambiguous names or even trivial programs will fail to type-check, just
>>> as Anthony said.
>>
>> Why special treatment for unambiguous names? They shouldn't be effected at
>> all by this.
>
> There are some design choices here as well, separately from the options
> above. Some possibilities are:
>
>  A. leave unambiguous names alone, and only do the special thing for the
> ambiguous ones (this doesn't break existing code, but can lead to
> confusing errors if an import is changed to introduce or remove an
> ambiguity, especially for options 2 or 3 above);
>
>  B. do the same thing for unambiguous names as ambiguous ones (but this
> may well break existing code, and is likely to restrict inference too much);
>
>  C. require an explicit syntactic cue that the name should be treated
> specially (e.g. the original TDNR's use of dot, or the # sign in the
> OverloadedLabels part of ORF [4]).
>
>
> As you can see, there are quite a few complex trade-offs here. I suspect
> this is at least part of the reason for the slow progress on TDNR-like
> extensions. It will be interesting to see how DuplicateRecordFields is
> received!
>
> All the best,
>
> Adam
>
>
> [1]
> https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/DuplicateRecordFields
>
> [2]
> https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/MagicClasses
>
> [3] https://phabricator.haskell.org/D1687
>
> [4]
> https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/OverloadedLabels
>
>
> --

Re: TDNR without new operators or syntax changes

2016-05-24 Thread Adam Gundry
Thanks for starting this discussion! Having spent more time thinking
about record field overloading than perhaps I should, here are some
things to think about...


On 22/05/16 16:01, Jeremy wrote:
> Bertram Felgenhauer-2 wrote
>>> 1. If the compiler encounters a term f a, and there is more than one
>>> definition for f in scope (after following all of the usual rules for
>>> qualified imports);
>>>
>>> 2. And exactly one of these definitions matches the type of a (or the
>>> expected type of f if given);
>>>
>>> 3. Then this is the definition to use.
>>
>> I now find that Anthony's concerns are justified. The question is, what
>> exactly does the type matching in step 2 involve? If it is a recursive
>> call to the type-checker then you'll have a huge performance problem.
> 
> I was concerned about this, but not knowing anything about how
> type-checking/inference is implemented, I wouldn't know if this is actually
> a problem or not.

Unfortunately this is indeed a problem. When the type-checker encounters
`f a`, it infers the type of `f`, ensures it is a function type `s ->
t`, then checks that `a` has type `s`. But if there are multiple
possible `f`s in scope, what should it do? Options include:

 1. run the entire type-checking process for each possible type of `f`
(this is almost certainly too slow);

 2. give ad-hoc rules to look at type information from the context or
the inferred type of the argument `a`;

 3. introduce a name resolution constraint and defer it to the
constraint solver (the same way that solving for typeclasses works);

 4. require a type signature in a fixed location.

Both 2 and 3 would need careful specification, as they run the risk of
exposing the type-checking algorithm to the user, and changing the
typing rules depending on what is in scope may be problematic. In
particular, if `f` has a higher-rank type than bidirectional type
inference is likely to break down.

The DuplicateRecordFields approach is to make use of bidirectional type
inference (a bit like 2, but without looking at the type of the
argument) and otherwise require a type signature. This is carefully
crafted to avoid needing to change existing typing rules. The wiki page
[1] sets out some of the cases in which this does and doesn't work.

Point 3 is rather like the magic classes in the OverloadedRecordFields
proposal [2] (this isn't in GHC HEAD yet, but an early version is on
Phab [3]).


>> If, on the other hand, you only take into account what is known about
>> the type of a at a given time, then you need special treatment for
>> unambiguous names or even trivial programs will fail to type-check, just
>> as Anthony said.
> 
> Why special treatment for unambiguous names? They shouldn't be effected at
> all by this.

There are some design choices here as well, separately from the options
above. Some possibilities are:

 A. leave unambiguous names alone, and only do the special thing for the
ambiguous ones (this doesn't break existing code, but can lead to
confusing errors if an import is changed to introduce or remove an
ambiguity, especially for options 2 or 3 above);

 B. do the same thing for unambiguous names as ambiguous ones (but this
may well break existing code, and is likely to restrict inference too much);

 C. require an explicit syntactic cue that the name should be treated
specially (e.g. the original TDNR's use of dot, or the # sign in the
OverloadedLabels part of ORF [4]).


As you can see, there are quite a few complex trade-offs here. I suspect
this is at least part of the reason for the slow progress on TDNR-like
extensions. It will be interesting to see how DuplicateRecordFields is
received!

All the best,

Adam


[1]
https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/DuplicateRecordFields

[2]
https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/MagicClasses

[3] https://phabricator.haskell.org/D1687

[4]
https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/OverloadedLabels


-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-22 Thread Jeremy
Bertram Felgenhauer-2 wrote
>> 1. If the compiler encounters a term f a, and there is more than one
>> definition for f in scope (after following all of the usual rules for
>> qualified imports);
>> 
>> 2. And exactly one of these definitions matches the type of a (or the
>> expected type of f if given);
>> 
>> 3. Then this is the definition to use.
> 
> I now find that Anthony's concerns are justified. The question is, what
> exactly does the type matching in step 2 involve? If it is a recursive
> call to the type-checker then you'll have a huge performance problem.

I was concerned about this, but not knowing anything about how
type-checking/inference is implemented, I wouldn't know if this is actually
a problem or not.


> If, on the other hand, you only take into account what is known about
> the type of a at a given time, then you need special treatment for
> unambiguous names or even trivial programs will fail to type-check, just
> as Anthony said.

Why special treatment for unambiguous names? They shouldn't be effected at
all by this.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/TDNR-without-new-operators-or-syntax-changes-tp5835927p5836393.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-22 Thread Jeremy
Henning Thielemann wrote
> I know people are unhappy with Haskell's records and module system, but I 
> still think that's because these language features are not used properly. 
> Type classes are the tool to write generic code and reduce combinatoric 
> explosion of functions and modules are a way to collect functions per 
> type. Following this principle you give function names that make sense 
> together with the module name like File.write or Channel.write. Then there 
> is no need for the compiler to disambiguate unqualified identifiers and 
> you keep the type and the module issues separated.

The issue is with importing third-party modules, where you can't combine
them into sensible type classes without writing you own abstraction layer.
And in some cases, the similarities are in name only, so type classes
wouldn't work in any case.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/TDNR-without-new-operators-or-syntax-changes-tp5835927p5836376.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-22 Thread Henning Thielemann


On Sun, 22 May 2016, Jeremy . wrote:


1. If the compiler encounters a term f a, and there is more than one definition 
for f in scope (after following all of
the usual rules for qualified imports);

2. And exactly one of these definitions matches the type of a (or the expected 
type of f if given);

3. Then this is the definition to use.



I know people are unhappy with Haskell's records and module system, but I 
still think that's because these language features are not used properly. 
Type classes are the tool to write generic code and reduce combinatoric 
explosion of functions and modules are a way to collect functions per 
type. Following this principle you give function names that make sense 
together with the module name like File.write or Channel.write. Then there 
is no need for the compiler to disambiguate unqualified identifiers and 
you keep the type and the module issues separated.


Today, if you stick to the unqualified style, and I guess you want to 
import modules without explicit identifier list, too, then your code can 
break whenever the imported modules add identifiers. In order to prevent 
this you have to use tight package import version bounds in your Cabal 
file. Your proposal would not solve this problem. Type-driven name 
resolution may disambiguate identifiers in some case but not in all ones, 
thus you still need to use tight version bounds.


The proposal seems to be a big complication. The compiler can no longer 
emit a message: "Type of function f mismatch", but it has to emit "If f 
means A.f, then the type error would be ..., but if it means B.f, then the 
type error would be ..." Or even worse: "If f means A.f and g means C.g, 
then the type error would be ... if f means B.f and g means C.g ... or f 
means A.f and g means D.g ..." The proposal also is more error-prone, 
because if you make a type-error this could be shadowed by a function in 
scope with a type that matches accidentally. A function with a very 
generic type and a generic name might be such an accidental match.


That said, the more complicated the proposals become the more one should 
reconsider about whether one runs in the right direction. I think this is 
the case here. The simple answer could be: Switch to a cleaner coding 
style!___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-22 Thread Jeremy .
Yes, that it indeed was I meant. AntC seems to be replying to a much more 
complicated/invasive proposal than what I had intended, apologies if I wasn't 
clear. (I see in retrospect that I may have misunderstood the original TDNR 
proposal, understandably leading to confusion.)


1. If the compiler encounters a term f a, and there is more than one definition 
for f in scope (after following all of the usual rules for qualified imports);

2. And exactly one of these definitions matches the type of a (or the expected 
type of f if given);

3. Then this is the definition to use.


That is all, although point 2 could be extended to consider the return type of 
f or other arguments as well. Even with the extension on, it would have no 
effect on programs which compile without it.


This has nothing to do with ORF, which relies on magic type classes (although 
there is some overlap in what it can achieve). The primary use-case I had in 
mind is disambiguating name clashes between local and/or unqualified imports.


Cross-posting to cafe and libraries as this doesn't seem to have attracted a 
lot of interest in users. Maybe it's just a boring proposal, maybe I didn't 
post it to the right list.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-21 Thread AntC
> Bertram Felgenhauer  googlemail.com> writes:
> ...
> I don't understand your conclusion.

Hi Bertram, I'm trying to tease out of Jeremy,
what he thinks his proposal amounts to.
Seeing as he's given very little clue so far.

So if I've arrived at an incorrect conclusion,
I want him to tell me where/what's gone wrong.

The point, I believe, although Jeremy's not said, is exactly as you say:

> Note that this has nothing to do with record fields at all, ...

So let's modify Jeremy's code snippet

> > > With syntaxless TDNR enabled, the last line could be:
> > > 
> > > f b c = do { reset b; reset c }

to something that's nothing to do with record fields:

 f b c = do { print b; print c }

`print` is a bare name appearing in a function application context.
It therefore needs disambiguating.
It's type :: (Show a) => a -> IO ()
Are `f`s params of type `a`, or of type (Show a) => a ? 
No, they're String or Int or whatever.
Compile fail.

Now you might say `print` doesn't need disambiguating.
Why not? Jeremy hasn't said.
Perhaps Jeremy intends a rule:
If there's only one version of the function in scope, choose that.
If so, Jeremy hasn't said. "syntaxless TDNR" doesn't give me a clue.
I don't think TDNR intended such a rule.

Suppose I do Jeremy's job for him and presume such a rule.

OK then. Second example:
Suppose I don't like what's happening with the FTP library changes,
specifically not the generalisation of `length`. So I write my own

import qualified Data.List as D
  -- note the qualified
length :: [a] -> Int. -- my version restricted to lists
length = D.length

Now I use length in a bare name function application

... (length [1, 2, 3, 4, 5]) ...

Therefore length needs disambiguating.
a) the disambiguator can't match argument type [Int] to [a].
b) even if it could, `length` remains ambiguous
 between my definition and the import.
 (As it happens, they're the same, but can the disambiguator tell that?
  Jeremy hasn't said what he thinks the disambiguator can do.
  But this is way beyond the original TDNR proposal.)

> Jeremy's proposal, I believe, is that the compiler should pick /the/
> possibility that type-checks ..

Well you're guessing what is the proposal, as much as I am.
In both the examples above, neither type checks.
(Or arguably both do if we allow polymorphic type checking.
 But should that allow both paramteric and ad-hoc polymorphic?
 Polymorphic checking is too generous for the way TDNR was spec'd.)

> Note that this has nothing to do with record fields at all,
> except that they give rise to a compelling use case.
> 

So the compelling use case has given us ORF Part 1 in GHC 8.0.
That has a clear antecedent in TDNR. But, pace your note,
it applies _only_ for record fields.
If you look at the implementation notes,
the functions derived from field labels
are specially flagged.
So disambiguation applies only to them,
not in general to bare function names.

> (I'm not endorsing the proposal, ...

Quite.

> ... just trying to clarify what it is.)
> 

Quite.

And since 8.0 is officially released as of this weekend,
I rather think "syntaxless TDNR", whatever it is/was, is stillborn.


AntC

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-21 Thread Bertram Felgenhauer
AntC wrote:
> > 
> > With syntaxless TDNR enabled, the last line could be:
> > 
> > f b c = do { reset b; reset c }
> > 
> 
> Heck, I didn't think you meant something that radical.
> So bare name in a function application context is to need disambiguating.
> 
> I think you'll find rather a lot of those in existing code.
> So this is a code-breaking change.

I don't understand your conclusion.

The code above, in context, is currently illegal: There are two "reset"
functions in scope, and the compiler will ask the programmer to specify
which of them they intended to use.

Jeremy's proposal, I believe, is that the compiler should pick /the/
possibility that type-checks (f had a type signature that would allow
only one combination to work); . Note that this has nothing to do with
record fields at all, except that they give rise to a compelling use
case.

(I'm not endorsing the proposal, just trying to clarify what it is.)

Cheers,

Bertram

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-19 Thread AntC
> Jeremy  hotmail.com> writes:

> > AntC wrote
> > I think you'll find rather a lot of those in existing code.
> > So this is a code-breaking change.
> 
> Could you give an example of existing code that would break?
> This certainly wasn't what I had in mind.

Then what do you have in mind?
"Do not break existing code" is not a design.
"Syntaxless TDNR" is not a design;
it's not even a thing.

I've given you two lengthy replies,
with pointers to further material.
You've given me two sentences,
and a snippet of code indistinguishable
from gazillions of bare name function calls 
in existing code.

I urge you (for the third time)
to look at ORF Part 1: Duplicate Record Fields.
See the type-directed resolution of label names.

AntC




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-18 Thread Jeremy
AntC wrote
> I think you'll find rather a lot of those in existing code.
> So this is a code-breaking change.

Could you give an example of existing code that would break? This certainly
wasn't what I had in mind.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/TDNR-without-new-operators-or-syntax-changes-tp5835927p5836060.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-18 Thread AntC
> 
> With syntaxless TDNR enabled, the last line could be:
> 
> f b c = do { reset b; reset c }
> 

Heck, I didn't think you meant something that radical.
So bare name in a function application context is to need disambiguating.

I think you'll find rather a lot of those in existing code.
So this is a code-breaking change.
The merit of adding an extension via new syntax,
is that in the places you didn't and don't use the syntax,
 nothing breaks.

Note that currently if you have in scope both a bare name
and that same name qualified,
the bare name applies, the compiler ignores the qualified one,
unless you deliberately write in the qualification.

How much are people deliberately playing with same name
bare and qualified? Probably seldom.
How much are people importing qualified
so they don't have to worry about their local name clashing?
Suddenly they'll have to start worrying.

So I see difficulties.
Perhaps TDNR's dot-apply would have suffered them too, but
* it was expected that dot-suffixing would only be used for field access
(and access to field-like functions)
* it was expected that the argument to the function would be near by,
so the compiler wouldn't have to look far for the type by which to resolve
* the debate around TDNR didn't get into this much detail,
because the dot syntax proposal met such a violent counter-reaction
* so TDNR never got beyond a wiki page, AFAIK.

One thing TDNR certainly suffers is that you still
 can't declare two distinct data types in the same module
with the same field name. ORF Part 1 in GHC 8.0 at least allows that.

Difficulties:
overloaded functions (methods) don't have a specific data type argument,
by which we could disambiguate the bare name.
(Disambiguation is supposed to be lightweight,
 we don't want to go hunting for instances.)
So a lot of the bare function names (eg imported from the Prelude)
are going to run into trouble.

In
f $ g $ h x
we have to disambiguate h to know its result type,
before we can disambiguate g, before we can disambiguate f.
Type improvement could rapidly get stuck.
Ah! but those are not bare names in a function application context.
So ($) contexts (and function composition (.) contexts)
are going to behave different to
f (g (h x))

But then your OP suggested users who want postfix apply
could define their own operator.
Presumably TDNR *is* to apply to that sort of function application(?)
So to ($) or not? to (.) or not? to sections or not?
to bare name functions supplied as arguments (to say map) or not?

I think this is the point SPJ would ask you to write up a proposal on a wiki,
to the same level of detail as all those other records proposals.


AntC

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-17 Thread Jeremy
AntC wrote
> No. For TDNR GHC needs some syntactic signal to trigger disambiguation.
> ...
> I suspect that if you took the syntax away from TDNR, you'd have very
> little left.

To copy an example from the TDNR wiki page:

  module Foo where
import Button( Button, reset ) as B
import Canvas( Canvas, reset ) as C

f :: Button -> Canvas -> IO ()
f b c = do { B.reset b; C.reset c }

With syntaxless TDNR enabled, the last line could be:

f b c = do { reset b; reset c }

This requires no syntactic signal. The compiler will see two candidate
definitions for reset, and in each case, pick the one which matches its
argument.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/TDNR-without-new-operators-or-syntax-changes-tp5835927p5835978.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: TDNR without new operators or syntax changes

2016-05-17 Thread AntC
> Jeremy  hotmail.com> writes:

Hi Jeremy, I feel your frustration at the slow evolution of records proposals.
There are many reasons, including that there has been much debate
and little consensus.

>
> Previous attempts to propose TDNR [1] have met with opposition over the
> accompanying proposal to change the syntax of the dot or add a new operator
> for postfix application.
> 
> However, nothing about TDNR - other than certain motivating examples -
> actually requires changes to the syntax of Haskell or new operators. ...

You are possibly confusing parts of one records proposal
with parts of TDNR.
In https://ghc.haskell.org/trac/ghc/wiki/Records/
DeclaredOverloadedRecordFields/DotPostfix
dot as postfix function apply could indeed be dispensed with.
But that is not within a TDNR approach.

> TDNR could be implemented as an extension which just give GHC
> a new way of disambiguating function names, and nothing else.

No. For TDNR GHC needs some syntactic signal to trigger disambiguation.
The idea was the dot (or some other operator) says "here comes a field label".
Without that signal, all GHC can see is a name 
-- could be a variable, a function, anything.

> 
> I would therefore like to propose TNDR without any syntax/prelude changes.
> 

I suspect that if you took the syntax away from TDNR,
you'd have very little left.

If there were a feasible records approach which needed no syntax/prelude
changes, I rather think it would have been found by now.
In terms of what's available now, have you looked at
 the lens approaches or Nikita's recent Anonymous Records?
https://ghc.haskell.org/trac/ghc/wiki/Records/Volkov

Have you looked at what's coming very shortly in GHC v8.0?
https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields
I suspect Part 1: Duplicate Record Fields
will go a long way towards disambinguating label names,
with only an occasional need for explicit type signatures.

How does that compare with TDNR minus syntax?


AntC



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


TDNR without new operators or syntax changes

2016-05-16 Thread Jeremy
Previous attempts to propose TDNR [1] have met with opposition over the
accompanying proposal to change the syntax of the dot or add a new operator
for postfix application.

However, nothing about TDNR - other than certain motivating examples -
actually requires changes to the syntax of Haskell or new operators. TDNR
could be implemented as an extension which just give GHC a new way of
disambiguating function names, and nothing else. This would still have some
advantages:

 - Redundant module qualification no longer required.
 - Unqualified imports could be changed to a different module with the same
interface (a very poor-man's backpack) without any other code changes.
 - People who want TDNR with postfix function application will only need to
define a simple postfix operator.

I would therefore like to propose TNDR without any syntax/prelude changes.

[1] https://prime.haskell.org/wiki/TypeDirectedNameResolution



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/TDNR-without-new-operators-or-syntax-changes-tp5835927.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users