Re: Magic classes for Overloaded Record Fields, overlaps, FunDeps

2016-05-15 Thread AntC
> Simon Peyton Jones  microsoft.com> writes:
> 

Hi Simon, I don't think there's an 'issue' in the sense fundeps 
can achieve something that type-families can't (or v.v.).
It's more about elegance and ergonomics of the code to achieve it.
(I'll try to avoid a question of judgment shading into a matter of taste ;-)

> |  > I have been vacillating between type families and fundeps for the ORF
> |  > classes. I hadn't fully appreciated this point about overlap, but I
> |  > think it is a reason to prefer fundeps, which is the direction in
> |  > which I'm leaning. I'd be grateful for feedback on this issue though!
> ...
> 
> |  The difficulty remains that as soon as you want overlaps in such a way
> |  that takes you to FunDeps, it's very difficult to 'mix modes' with type
> |  families.
> 
> Can one give a standalone explanation of the fundep/type-family/overlap
> issue here? 
> Or is it explained on a wiki page?
> 

Neither is it specifically about the Overloaded Record Fields design,
nor anonymous records -- it's just that you need a meaty application
like those to demonstrate the subtleties.

I've taken some time to review what's explained where.
I think most of it has come up before, scattered various places.
I see 4 inter-related pieces.
I'll volunteer to write these up, if somebody would like to tell me where.

1. ORF has chosen the `Has` class to be implemented using FunDeps,
rather than type families.
The motivation (for 'option 1') is documented on the wiki,
pointing to the original design (with which you were involved). 
https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Design

Choosing FunDeps is right if we move on to anonymous records,
which are bound to face some egregious overlaps, so...

2. Adam's point (and example) about overlap of instances wrt 
anonymous records, has been 'in the wind' before -- e.g. comment here
https://typesandkinds.wordpress.com/2013/04/29/coincident-overlap-in-type-
families/#comment-152
 Detecting the unwanted ambiguity of instance satisfaction
 is discussed in the HList paper's `Lacks` constraint.

3. There's a clumsiness in type families faced with such examples.
Really you want to put an equation in a closed type family
to 'trap' or guard against the ambiguity.
But in effect say "treat this as an error, not a proper instance".
So the Instance Chain work (for example) has a 'fails' outcome.

4. When you've decided to implement some piece using FunDeps,
It works OK to delegate some of the type-level calculations to
(possibly closed) type families, per Adam's response to my q on this thread.
But v.v. if you have some piece using type families,
and then want to delegate to FunDeps because of nasty overlaps;
that tends to get awkward.
It's better than it was with the first releases of type families.


AntC


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


Re: Magic classes for Overloaded Record Fields, overlaps, FunDeps

2016-04-27 Thread AntC
>
> The labelled "birthday = ..." approach seems
> tantalisingly close to data constructors:
>( Name "Fred", Birthday $ Date 28 4 2016 )
>
> Which takes us (perhaps) to HLIst-style
> Type-Indexed Products.
> How could they fit with ORF?
> Perhaps introduce an implicit label spelled same as the Data Constructor?

Errk! That should be Type Constructor.
(I'm expecting these would be newtypes
with the Data Constructor punning on the Type.)

Thinking on ...

Having been unkind about the higher-kinded stuff,
[I withdraw and apologise.]
I wonder if we could use it?
Does this have any likelihood of working?

import Data.Kind
class IskLabel k (x :: k) a where fromkLabel :: Proxy# x -> a
instance IskLabel Symbol x (r -> a) where ...
 -- indexing by label
instance IskLabel (Type -> Type) t (r -> a) where ...
 -- indexing by Type Constructor

> Except starting lower case,
> otherwise the #name prefix will throw a wobbly.

??Is that actually true?
H98 field labels must be lower case,
so all the examples are.
But Symbol can be upper??


AntC

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


Re: Magic classes for Overloaded Record Fields, overlaps, FunDeps

2016-04-27 Thread AntC
> Adam Gundry  well-typed.com> writes:
> ...
> 
> P.S. If you have any thoughts on the interaction between ORF and
> encodings of anonymous records, I'd be interested to hear them.

Are you sure you want to open up that question? ;-)
Nikita's record library has certainly given food for thought.

Before we start into anonymous records,
I think we should figure out the path that gets to
extensible records, truncatable records, mergable records,
joinable records, ...
So I'm worried about comments from Nikita
that extensibility is beyond what's possible under that approach.

In considering that, I'm not sure that "anonymous records" are very much
like H98 field-labelled data types.
(Which is to say H98 records are not very much like records ;-)
Trouble is, H98 records have gobbled up so much of the available syntax.

Let's frame the requirement instead as 'labelled tuples'.
Then I'm looking greedily at round-bracket syntax:

( name = "Fred", birthday = (day = 28, month = 4, year = 2016) )

I don't know how much Nikita was limited by what's possible
with src-xtns, so I won't bikeshed more about syntax.

Can we use the same ORF mechanisms under the covers
for both labelled tuples and records?
Certainly it would be nice to support intra-conversion routines:

labelledDT = fromLabels ( name = ... )
labelledTuple = toLabels labelledDT

I rather think I don't care about the implementation of access
-- that is, whether lenses and which style of lens --
providing it just works. (And doesn't give impenetrable
error messages. That's a bit of a worry with all this higher-kinded
engineering going on in GHC 8.0.
Will ORF's 'Magic Type Classes' have bit-rotted
by the time you get to release them?
Do we call that R.Eisenberg uncertainty? ;-)

Now if you have a label "birthday",
you probably want the field to hold a Date,
not just some arbitrary type 'a'.
And that's what I find unergonomic about the 
label-as-Symbol approach.
(For Nikita's records you give a type for the field alongside the label
 in the record signature.
 But why the need to state the obvious,
 and repeat it for every record that uses "birthday"?)

The labelled "birthday = ..." approach seems
tantalisingly close to data constructors:
( Name "Fred", Birthday $ Date 28 4 2016 )

Which takes us (perhaps) to HLIst-style
Type-Indexed Products.
How could they fit with ORF?
Perhaps introduce an implicit label spelled same as the Data Constructor?
Except starting lower case,
otherwise the #name prefix will throw a wobbly.

What gave me a queasy feeling looking at Nikita's Records
is the alternating labels and data type.
  ::  Record2 "name" String "birthday" Date

I'd rather see explicit pairing of label and data.

newtype Label (l :: Symbol) a = Label a
rec :: Record2 (Label "name" String, Label "birthday" Date)

The newtype should mean zero runtime cost.

I can see a couple of reasons behind Nikita's approach
that might have been getting in the way of that.

Sequencing the labels into alphabetic order.
(Which is probably to implement the second reason.)
Now certainly we want the label position to be arbitrary
in anonymous records. But that's just a bit of representation hiding.
Resequencing them alphabetically means they show
in a probably unmeaningful format.
It also might be getting in the way of extensibility. 
To compare two records with the same labels,
does need the fields in the same seq.
We could do that with:

labelledTuple `asLabelSeqOf`canonicalLabels

The second reason would be to check for duplicate labels.
Hmm is that essential? YMMV
As far as I can see, duplicate labels within a tuple
are only problematic when you want to get/set
a field by that label.
Your example [1] isn't upset by:
  z4 = getField (proxy# :: Proxy# "bar") (Record3 True False "ok"
   :: Record3 "foo" Bool "foo" Bool "bar" String)

Again if it is a requirement,
it's easy enough to build a smart constructor wrapper
that validates for duplicate labels, รก la HList.


Did that answer (any of) your question?

AntC

> 
> [1] https://gist.github.com/adamgundry/7292df8cef62fd6750885be3f5f892e7
> 
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


RE: Magic classes for Overloaded Record Fields, overlaps, FunDeps

2016-04-27 Thread Simon Peyton Jones
|  > I have been vacillating between type families and fundeps for the ORF
|  > classes. I hadn't fully appreciated this point about overlap, but I
|  > think it is a reason to prefer fundeps, which is the direction in
|  > which I'm leaning. I'd be grateful for feedback on this issue though!
...

|  The difficulty remains that as soon as you want overlaps in such a way
|  that takes you to FunDeps, it's very difficult to 'mix modes' with type
|  families.

Can one give a standalone explanation of the fundep/type-family/overlap issue 
here? Or is it explained on a wiki page?

Simon

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


Re: Magic classes for Overloaded Record Fields, overlaps, FunDeps

2016-04-26 Thread AntC
> > On 26/04/16 09:20, AntC wrote:
> > There's an intriguing comment here wrt anonymous records: ...
> 
> I'm afraid the sentence on the wiki page is slightly misleading, ...
>  with the change to functional dependencies,
> the overlapping instances solution works rather nicely, 
> in that it works if the field labels are distinct
> and reports an error if not [1]. 

Thanks Adam, we're very much thinking along the same lines.

Yes that's exactly where I am at.
I too like the error message re overlapping instances.

Contrast that for an HList style solution,
you get instance match on the leftmost/outermost appearance
of the label. So to detect duplicates you need a `Lacks`
superclass constraint on the HList's tail.
And to get `Lacks` to work,
you need to create an instance;
for which you then need an impossible-to-fulfill
superclass constraint.
Even with the best of documentation,
you get a dense error message,
quite possibly pointing to the wrong place.

So unlike HLists, Nikita's Records are 'flat'
(same as if you used plain tuples)
and the instance matcher can look at all elements at the same time.

Furthermore (closed) type families suffer a similar difficulty.
The instance equations are ordered, so will pick the leftmost
(or rightmost) appearance without complaint.
To detect ambiguous getFields you need first a guard equation
   HasField n1 (Record2 n1 v1 n1 v2) = error: overlap

For a two-tuple that's OK.
For more than two you need guard equations
for all of the ambiguous perms and combs.
For a 24-tuple that's horrendous.
For tuple extension or joining your head explodes.

Even if we could automate generating the ambig instances somehow,
it just feels wrong to get an instance/equation match
when what you want is an error.

> 
> I have been vacillating between type families and fundeps for the ORF
> classes. I hadn't fully appreciated this point about overlap, but I
> think it is a reason to prefer fundeps, which is the direction in which
> I'm leaning. I'd be grateful for feedback on this issue though!
> 

Yes, this seems a 'featurette' of Overlaps/FunDeps
compared to closed type families.
Should I regard it as a 'happy accident'
 that might stop working some day?
It does seem a pretty fundamental requirement for Overlaps
-- providing of course IncoherentInstances is never switched on
in some distant module.

> 
> In general, to avoid overlapping instances, one trick is to introduce a
> closed type family that discriminates between the parameters, 
> along with an auxiliary class whose instances match
>  on the result of the type family. ...

Thanks. Yes I'm aware of that approach from HList.
It works a little more nicely with type families.

The difficulty remains that as soon as you want overlaps
in such a way that takes you to FunDeps,
it's very difficult to 'mix modes' with type families.


AntC

> 
> [1] https://gist.github.com/adamgundry/7292df8cef62fd6750885be3f5f892e7
> 




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