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


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


Re: Closed Type Families: type checking dumbness? [was: separate instance groups]

2015-06-08 Thread AntC
 Dan Doel writes:
 
 It seems to me the problem is that there's no way
 to define classes by consecutive cases to match the family definitions.

Thanks Dan, yes we've an impedance mis-match.

Closed logic for type families;
Open (or Distributed) logic for class instances.

I see two possible fixes:
1. Closed logic for class instances

 I don't know what a good syntax for that would be,
 since 'where' syntax is taken for those.

Indeed. We could follow SQL and use 'HAVING' ;-)

2. Open/Distributed logic for type families
   (and class instances).

Take the example type family:

     type family F a    where
       F (Foo Int c)  = Int  
       F (Foo b Char) = Char

For instance selection to move confidently
from the first to the second equation,
it must satisfy itself that Foo's first arg
could not possibly be Int. ie (b /~ Int)

Let's expose the compiler's internal workings
into the surface lang.
And annotate that on the second equation as

F (Foo b Char) | (b /~ Int) = Char

This mirrors the syntax for pattern guards.

Now no usage site could ever match both equations.
(And we can prove that as we validate each instance.)
So we could 'float' the type  instances away
to appear with the class instances
-- even as Associated types.
(And we'd need type disequality guards
 on the class instances.)


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


Re: Closed Type Families: type checking dumbness? [was: separate instance groups]

2015-06-08 Thread AntC
 Richard Eisenberg writes:
 
 This is all expected behavior. ...

Thank you Richard. So to be clear what it is that's expected:

For any class with overlapping instances
that calls on a Closed Type Family,
for all [**] instances,
expect to put a type equality constraint,
whose LHS is exactly the instance head,
and whose RHS is exactly the RHS
of the corresponding type family equation.
IOW expect the type equation to appear twice
(with `=` changed to `~`, modulo alpha renaming).

Note [**] not quite all instances.
The instance whose head is the first family equation
can have the constraint omitted.

 GHC's lazy overlap checking for class instances ...

Hmm? I don't think it's the lazy checking
of whether overlapping instances apply at a use site.
I think it's the eager checking
at the instance declaration.

 ... I'm afraid I don't see what can be improved here.

Two suggestions:
1. Automatically generate the type eq constraint.
   (Or at least suggest that as a Possible fix
in the error message.)
2. Don't bother with a type family in such cases.
   Instead use Overlaps with FunDeps.
   (And needs UndecidableInstances.)

  On Jun 6, 2015, at 2:04 AM, AntC wrote:
  needs the eq constraint. Without it, GHC complains:
 Couldn't match expected type ‘F (Foo b Char)’
 with actual type ‘Char’
 Relevant bindings include
   f :: Foo b Char - F (Foo b Char)
 In the expression: y
 In an equation for ‘f’: f (Foo _ y) = y
  
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Closed Type Families: type checking dumbness? [was: separate instance groups]

2015-06-06 Thread AntC
 From: AntC 
 Date: 2015-06-04 22:39:25 GMT 

 Take the standard example for partial overlaps.
 Suppose I have a class: ...

 I'm also getting (in more complex examples)
 GHC complaining it can't infer the types
 for the result of f.
 So now I'm having to put type equality
 constraints on the class instances,
 to assure it that F comes up with 
 the right type.

In a reduced example, I'm still getting 
poor type checking. This is GHC 7.8.3.
This seems so dumb, I'm suspecting a defect,
It's similar to
but much more glaring than:
https://ghc.haskell.org/trac/ghc/ticket/10227
https://ghc.haskell.org/trac/ghc/ticket/9918

{-# LANGUAGE TypeFamilies,
 FlexibleInstances
   #-}
module ClosedTypeFamily where

data Foo b c = Foo b c deriving (Eq, Read, Show)

type family F awhere
  F (Foo Int c)  = Int-- Foo Int is first instance
  F (Foo b Char) = Char

class C a where f :: a - F a

instance C (Foo Int c) where  -- compiles OK
  f (Foo x _) = x

instance (F (Foo b Char) ~ Char) = C (Foo b Char) where
  f (Foo _ y) = y

needs the eq constraint. Without it, GHC complains:
Couldn't match expected type ‘F (Foo b Char)’
with actual type ‘Char’
Relevant bindings include
  f :: Foo b Char - F (Foo b Char)
In the expression: y
In an equation for ‘f’: f (Foo _ y) = y

Note that if I change the sequence 
of the family instances for F,
then GHC instead complains
about the class instance for (Foo Int c).

OK these are overlapping class instances.
But GHC's usual behaviour
(without closed type families)
is to postpone complaining
until and unless a usage
(Foo Int Char) actually turns up.

BTW if I put a first family instance
  F (Foo Int Char) = Int
to explicitly catch the overlap,
then GHC complains about **both** class instances.

Reminder [to Richard]
I need not only types but also terms.

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


Re: Closed Type Families: separate instance groups?

2015-06-04 Thread AntC
 Simon Peyton Jones simonpj at microsoft.com writes:
 
 I think it's pretty good as-is.
 
Thank you Simon, I'm agreeing with pretty good,
though possibly not with pretty ;-)

 ...
 * Use a closed family (with overlap and top-to-bottom matching)
to deal with that part of the space:
 
 Doing this was a HUGE improvement, ...

(I'm not quite getting improvement over what?
 This was and is the only way to do overlaps with Type Families?)

I'm not ever-so sure I'm seeing an improvement
over overlapping class instances with FunDeps.
I really really want type families to be an improvement
because type manipulation in a functional language
should be -- errm -- functional.

 |  It also BTW cuts us off from using Closed Families as Associated types
 |  separated into their Class instances.
 
 I don't understand this comment. ...

I'll answer Richard's strapline at
https://typesandkinds.wordpress.com/
Who needs terms, anyway?:
I need both types and terms.

Yes the compiler needs first a type-solving phase
before dealing with the terms.
Type Families cleanly separate that off.

And in a significant proportion of use cases,
the type-handling is the same across many class instances.
So it's more succinct to collapse the type instances
into a grouped type family ... where ...

There's other use cases for overlapping
where you can't collapse the type-handling.
So then I'm finding that my class instances
have heads that repeat the type instance heads.
And I would use Assoc types
but the type family instances
have to appear in the family, to sequence the top-to-bottom matching.

 Can you give an example that the current setup does not handle?
 
(This is about dealing with many instances,
 so difficult to give a succinct example.
 And the current setup does handle it OK.
 It's just that it seems verbose, with hard to read code,
 compared to FunDeps. I appreciate that's in the eye of the beholder.)

Take the standard example for partial overlaps.
Suppose I have a class:

class C a where f :: a - F a

instance C (Foo Int c) where
   -- I'd like to put
  type F (Foo Int b) = Int   -- but it overlaps
  f (Foo x _) = x

instance C (Foo b Char) where
  type F (Foo b Char) = Char -- non-confluent
  f (Foo _ y) = y

Imagine there's dozens of overlapping instances.
(And BTW there's no actual ambiguous usages.
 By construction (Foo Int b) means b /~ Char.
 But I have no way to declare that.)

I'm also getting (in more complex examples)
GHC complaining it can't infer the types
for the result of f.
So now I'm having to put type equality
constraints on the class instances,
to assure it that F comes up with 
the right type.
This just seems easier if I have the result type
as an extra param to the class,
with a FunDep in the classic style:

class C a b | a - b where
  f :: a - b

(I can supply those more complex examples if need be,
 but this post is already too long.)

AntC



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


Re: Closed Type Families: separate instance groups?

2015-06-03 Thread AntC
 Richard Eisenberg eir at cis.upenn.edu writes:

 You can always define a helper closed type family
 and have an open type family instance just call a closed type family. 

Thank you Richard, you mean like:

type family OpenF a

...

type instance OpenF (Foo b c) = FFoo (Foo b c)
type family FFoo a where
  FFoo (Foo Int c) = ...
  ...

OK. (Seems rather verbose.)

 
 Having closed type families, as opposed to branched instances,
 just seemed like a cleaner way to package the new functionality.
 There really wasn't much to it other than aesthetics,
 if I recall the conversations correctly.

I recall the conversation quite well.
(In fact I think it was me who suggested type family ... where ... )
I think it was less to do with aesthetics,
and more to do with reducing verbosity in a common use case.

It somehow doesn't seem as clean as old-fashioned overlapping instances.
(I agree it does seem cleaner than overlaps with FunDeps.)

It also BTW cuts us off from using Closed Families as Associated types
separated into their Class instances.
I think there's two use cases going on:
- one where we want to see all the instances together
   that fits well to type family ... where ...
- t'other where we want everything to do with a type constructor together
   that fits better with the separate instances

AntC



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


Closed Type Families: separate instance groups?

2015-06-03 Thread AntC
Currently (GHC 7.8.3) the only form for Closed Type Families is:

type family F a where ...
  -- list your instances here

(This was considered a common use case
 -- for example in HList to put the type-matching instance
 with the non-matching, and that would be total coverage;
 rather than needing a type family decl and an instance decl
 with the instance head same as family.
 That was an optimisation over ...)

Way back the design was more like this:

type family F a

type instance F (Foo b c)  where
  F (Foo Int c) = ...
  F (Foo b Char) = ...

type instance F (Bar e f g) where
  F (Bar Int f g) = ...

The idea was that the separate instance groups must have non-overlapping heads.

This is handy if Foo, Bar, etc are declared in separate places/modules.
You can put the instances with the data decl. 
And quite possibly the family decl is in an imported/library module 
you don't want to touch.

Is this separate instance group idea still a gleam in someone's eye? 
If not, is there some deep theoretical reason against?

AntC

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


Re: Overlapping and incoherent instances

2014-07-30 Thread AntC
 Simon Peyton Jones simonpj at microsoft.com writes:
 Tue Jul 29 09:11:05 UTC 2014
 ...
 This is a Big Hammer. 

I agree with Simon's motivation that the whole-module overlap pragma is 
often too brutal.

But I think that what Iavor has developed is still too brutal.
(Sorry, and I hadn't known about these instance-level pragmas before now.)

For my 2d, I think Andreas made an important distinction:

 Andreas Abel andreas.abel at ifi.lmu.de 
 Wed Jul 30 12:07:01 UTC 2014
  The German equivalent of overlap, ..., is used exclusively in a 
 symmetrical fashion.  It's like in English, if I say our interests 
 overlap, then it is pointless to ask whether my interest are 
 overlapping yours or are overlapped by yours.

I'd say that the English overlap is also used in a symmetrical fashion
(outside of specialist Haskell instances usage).

There's a difference between:
- this instance is nec. narrower than some other instance
  (IOW anything that's a substitution for this instance,
   is ipso facto a substitution for some wider)
- vs. a partial overlap
  (some substitutions will fit this instance only,
   some will fit another instance, not this one,
   some will fit both)

In my experience, unintended partial overlaps are the nastiest to diagnose.
And partial overlaps are very seldom needed in practice.
They're often a symptom that two separately-developed libraries are 
clashing.

(For example the HList libraries -- as originally released --
 used overlap extensively, but no partial overlaps.)

So I would like the pragmas to be able to say:
OK for this instance to subsumes or be subsumed by some other instance
but it must not partially overlap any instance.

(I guess this is beyond the question Simon's OP asked.)


AntC


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


Re: Liberalising IncoherentInstances

2013-07-30 Thread AntC
 Axel Simon Axel.Simon at in.tum.de writes:

 ...
 
 In recent years I acquired the view that 
 type inferences should have some sort of semantic completeness property 
 ...

If you want 'semantic completeness', don't use IncoherentInstances.

(As several have said, it's not a popular extension;
more of a 'necessary evil' to use with caution.
That's why it's a good suggestion to limit it's 'reach'
to particular instances.)

The price to pay for avoiding IncoherentInstances might be:
- adding extra instances to avoid partial overlap
- adding type annotations
- 'helper' classes to resolve type-ambivalent instances
  (see Oleg's work for examples of these)
- fancy uses of FunDeps
- ultimately, programs that fail to compile

 ... With semantic completeness I mean the best possible type
 that that can be expressed by the type language. ...

If there is a (unique) 'best possible type',
then you don't need IncoherentInstances, IMO.


AntC


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


Re: Liberalising IncoherentInstances

2013-07-29 Thread AntC
 AntC anthony_clayden at clear.net.nz writes:

Uh-oh, quoted the wrong example. I mean:
 
Starting with:

class C a b | a - b where foo :: a - b
instance C [a] [a] where foo = id

t11 = \x - foo [x] -- t11 :: t - [t]

I then added:

instance C [Char] [Char] where foo = id
 -- more specific!
t12 = \x - [x]  -- t12 :: C [t] [t] = t - [t]
 -- more polymorphic!



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


Re: Liberalising IncoherentInstances

2013-07-28 Thread AntC
 Simon Peyton-Jones simonpj at microsoft.com writes:
 
 I've realised that GHC's -XIncoherentInstances flag is,
 I think, over-conservative. 

Hi Simon, by coincidence I've just come across a very similar issue with 
overlapping instances and FunDeps (following-up some discussion with Oleg, 
MartinS, EdwardK).

Starting with:

class C a b | a - b where foo :: a - b
instance C [a] [a] where foo = id

t1 = foo a -- t1 :: [Char] - [Char]

I then added:

instance C [Char] [Char] where foo = id
 -- more specific!
t2 = foo a -- t2 :: C [a] [a] = [a] - [a]
 -- more polymorphic!

My (probably subjective) experience is that somewhere around 2006 when 
Type Families started appearing, there were some subtle changes around 
overlaps. TF's seemed to be very pre-occupied with supporting 'coincident' 
(or confluent) _partial_ overlap.

(By partial overlap I mean: some substitutions match both instances, some 
only one, some only t'other. This seems to be the root of the issue with 
Joachim's post on ghc-devs.)

Partial overlaps are always going to be awkward for IncoherentInstances. 
With Type Families, you can always check that the result is confluent. But 
for class instances there's no such algebraic/semantic check possible.

It's easy to avoid partial overlaps: just define an instance for the mgu 
of the overlap; then both of the less-specific instances totally overlap 
it.

With the benefit of hindsight, I would have banned partial overlaps. IMO 
we could then validate class instance 'eagerly' at point of declaration 
(as Hugs does), rather than paying the penalty later with hazy/lazy 
instance selection woes.

I strenuously try to avoid needing IncoherentInstances. I've no objection 
to your proposed liberalise a bit.


 
 Incidentally, I think it'd be an improvement to localise the 
Overlapping/Incoherent flags to particular
 instance declarations, via pragmas, something like
   instance C [a] where
 {-# ALLOW_OVERLAP #-}
 op x = 
 
 Similarly {-# ALLOW_INCOHERENT #-}.   Having -XOverlappingInstances for 
the whole module is a bit crude.,
 and might be missed when looking at an instance.   How valuable would 
this be?
 

+1
I strongly support localising these flags. Very seldom do I want 
Overlapping for every class in a module, and I'd rather the compiler told 
me if I inadvertently did overlap an instance.

Better still, can we do {-# DISALLOW_PARTIAL #-} ?



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


Re: Field accessor type inference woes

2013-07-05 Thread AntC
 Adam Gundry adam.gundry at strath.ac.uk writes:

  On 04/07/13 12:27, AntC wrote:
  H-R fields are a limitation because we can't update them either. So I
  think it's a fair question whether supporting h-r polymorphism is
  worth the limitations?
 
 Yes, higher rank polymorphism is bound to cause trouble with polymorphic
 projections, and perhaps it won't matter if we limit ourselves to one or
 the other.
 

So with h-r fields, let's stratify the requirements:
* The current Plan tries to support holding h-r fields
  in a way backwards-compatible with H98 records.
  Why? We know that OverloadedFields are going to break some stuff.
  It's a question of which stuff is more important to not break.

* I think the real requirement is to hold an h-r value
  in a record, accessible by field name.

Consider TPDORF does this:
(see example based on one in SPJ's SORF 
http://hackage.haskell.org/trac/ghc/wiki/Records/TypePunningDeclaredOverloa
dedRecordFields#Implementation:theHasclasswithmethodsgetandsetandpunnedType
s at 'Higher-Ranked polymorphic fields' )

  -- must wrap h-r values in a newtype to put them in a record.
newtype Rev = Rev (forall a. [a] - [a])
data HR = HR { rev :: Rev }

  -- Has class takes 2 args, with type family for GetResult
type instance GetResult r rev = Rev
instance Has HR rev where
getFld HR{ rev = (Rev x) } = Rev x
-- can't unwrap here, 'cos can't spec Polymorphic

Then user code must unwrap the newtype at point of applying.

I think this approach also allows update for h-r values (providing they're 
wrapped) -- but I must admit I rather ran out of steam with the prototype.


TPDORF also supported type-changing update for parametric polymorphic 
fields -- but with limitations. To get round those you would have to 
revert to H98 record update -- just as the current Plan.

So I'm tending to the conclusion that cunning though it is to use 
a functional-dependency-like mechanism (but using equalities) 
for the result type,
that is actually giving too much of a headache.

**bikeshed:
I do like the proposed sugar for constraints (r { f :: t }) = ...
But how does that play if `Has` only needs 2 args?


AntC



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


Re: Field accessor type inference woes

2013-07-02 Thread AntC
 
 I was envisaging that we might well need a functional dependency
 

Hi Adam, Edward, (Simon),

I think we should be really careful before introducing FunDeps (or type 
functions).

Can we get to the needed type inference with UndecidableInstances?
Is that so bad?

In the original SORF proposal, Simon deliberately avoided type functions, 
and for closely argued reasons:
But this approach fails for fields with higher rank types.
I guess the same would apply for FunDeps.

FWIW in the DORF prototype, I did use type functions.
I was trying to cover a panoply of HR types, parametric polymorphic 
records, type-changing update [**], and all sorts; 
so probably too big a scope for this project.

If you're interested, it's deep in the bowels of the Implementation notes, 
so I could forgive anybody for tl;dr. See:
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFi
elds/ImplementorsView#Type-changingupdate

In terms of the current Plan:

class Has r fld t   where
getFld  :: r - GetResult r fld t

Of course where the record and field do determine the result,
the GetResult instance can simply ignore its third argument.
But for HR types, this allows the `Has` instance to 
'improve' `t` through Eq constraints,
_and_then_ pass that to GetResult.

In the 'chained' accessors that Edward raises,
I think the presence of the type function 'fools' type inference into 
thinking there's a dependency.

So (foo . bar) has type (and abusing notation):

( Has r bar t_bar, Has (GetResult r bar t_bar) foo t_foo )
 = r - (GetResult (GetResult r bar t_bar) foo t_foo)


[**] Beware that the DORF approach didn't support type-changing update in 
all cases, for reasons included in the notes for Adam's Plan page.

Also beware that DORF used type families and some sugar around them.
That had the effect of generating overlapping family instances in some 
cases -- which was OK, because they were confluent.
But if I understand correctly what Richard E is working on
http://hackage.haskell.org/trac/ghc/wiki/NewAxioms
overlapping stand-alone family instances are going to be banished
-- even if confluent.
So today I would approach it by making them associated types,
and including the GetResult instance inside the `Has`,
so having a separate (non-overlapping) instance
for each combination of record and field (Symbol).

HTH. Is Adam regretting taking up the challenge yet? ;-)

AntC


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


Re: Field accessor type inference woes

2013-07-02 Thread AntC
 Simon Peyton-Jones simonpj at microsoft.com writes:
 
  ...; it’s a tradeoff between polymorphism and overloading.
  

Hah! my post crossed with Simon's. This time I'll be succinct.
There's **three** alternatives. ...


   data R a = MkR { foo :: a - a }
   data S    = MkS { bar :: forall b. b - b }
  

Try Plan C: use a cleverer (associated) type function

class Has r f twhere
   type GetResult r f t :: *   -- ?? default to t
   getFld :: r - GetResult r f t

    instance (t ~ a-a) = Has (R a) “foo” t where
   type GetResult (R a) foo t = a - a   -- ?? ignore t
   getFld ...
    instance (t ~ b-b) = Has S “bar” t where 
   type GetResult S bar t = t  -- 'improved' t
   getFld ...

In the 'chained' accessors that Edward raises,
I think the presence of the type function 'fools' type inference into 
thinking there's a dependency.

So (foo . bar) has type (and abusing notation):

( Has r bar t_bar, Has (GetResult r bar t_bar) foo t_foo )
 = r - (GetResult (GetResult r bar t_bar) foo t_foo)





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


Re: Overloaded record fields

2013-06-30 Thread AntC
 Malcolm Wallace malcolm.wallace at me.com writes:
 
 I believe Simon's point is that, if dot is special, we can infer 
the Has type above, even if the compiler is
 not currently aware of any actual record types that contain a foo 
field. ...
 
 (For the record, I deeply dislike making dot special, ...

Simon, Malcolm, here's a solution (at risk of more bikeshedding on syntax).

e { foo }

  * The braces say 'here comes a record'.
  * Also say 'expect funny business with names'.
  * The absence of `=` says this is getFld, not update.
  * This is not currently valid syntax [**], so we don't break code.
  * It's postfix. (And only a couple more chars than infix dot.)
  * So perhaps an IDE can see the opening brace and prompt for fields?
(Perhaps some IDE's do this already for record update?)
  * If we need to disambiguate the record type:

e :: T Int { foo }   -- as the Plan suggests for record update

Development would fit into the 'sequence of attack' as 5b., with record 
update syntax.

[**] ghc 7.6.1 rejects the syntax, and suggests you need NamedFieldPuns.
 But if you set that, you get a weird type error,
 which suggests ghc is de-sugaring to { foo = foo }.
 We'd have to fix that.

The syntax is valid in a pattern (with NamedFieldPuns).
Indeed the proposed syntax echoes pattern match:

e .$ (\ (MkFoo { foo }) - foo )   -- (.$) = flip ($)

We'd better insist NamedFieldPuns is on to allow the proposal.
Otherwise the syntax would have to be:

e { foo = foo } -- ambiguous with update

In fact the proposal is an enhancement to NamedFieldPuns,
'repurposed' for OverloadedRecordFields.

Possible future development:

e { foo, bar, baz }  -- produces a tuple ( _, _, _ )
 -- with fields in order given
 -- _not_ 'canonical' order in the data type

  * By coincidence, that syntax is per one of the dialects for
relational algebra projection over a tuple.

  * Possibly useful for overloaded comprehensions?:

[ x { foo, bar, baz } | x - xs ]

[ { foo, bar } | { foo, bar, baz } - xs, baz = 27 ]


AntC


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


Re: A possible alternative to dot notation for record access

2013-06-30 Thread AntC
 Carter Schonwald carter.schonwald at gmail.com writes:
 
 indeed, this relates / augments record puns syntax already in 
GHC http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-
extns.html#record-puns.
 

Uh-oh. That documentation gives an example, and it exactly explains the 
weird type-level error I got when I tried to use the proposed syntax 
myself:

Note that: 

*   Record punning can also be used in an expression, writing, for 
example, 

let a = 1 in C {a}-- !!!

instead of 

let a = 1 in C {a = a}

The expansion is purely syntactic, so the expanded right-hand side 
expression refers to the nearest enclosing variable that is spelled the 
same as the field name. 

IOW the proposal _does_ conflict with existing syntax. (And I guess I can 
see a use for the example. Note that outside of that let binding, `a` 
would be a field selector function generated from the data decl in which 
field `a` appears -- that's the weirdity I got.)

I suppose the existing syntax has a data constructor in front of the 
braces, whereas the proposal wants a term. But of course a data 
constructor is a term. 

So the proposal would be a breaking change. Rats! Is anybody using that 
feature?

 
 On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson judah.jacobson at 
gmail.com wrote:
 
 Unlike dot notation, this is unambiguous and doesn't conflict with any 
existing syntax (AFAIK). ...


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


Re: Overloaded record fields

2013-06-28 Thread AntC
 Simon Peyton-Jones simonpj at microsoft.com writes:
 
 I have, however, realised why I liked the dot idea.  Consider
 
   f r b = r.foo  b
 

Thanks Simon, I'm a little puzzled what your worry is.

 With dot-notation baked in (non-orthogonally), f would get the type

   f :: (r { foo::Bool }) = r - Bool - Bool
 
 With the orthogonal proposal, f is equivalent to
   f r b = foo r  b
 
 Now it depends. 
 
 * If there is at least one record in scope with a field foo 
   and no other foo's, then you get the above type
 

I don't think the compiler has to go hunting for 'records in scope'.
There is one of two situations in force:

Step 6. -XNoMonoRecordFields  
Then function foo is not defined.
(Or at least not by the record fields mechanism.)
This is exactly so that the program can define
its own access method (perhaps lenses,
 perhaps a function foo with a different type,
 the namespace is free for experiments).

Step 7. -XPolyRecordFields
Then function foo is defined with the same type
as would be for (.foo) in the baked-in approach. IOW

f r b = (.foo) r  b -- baked-in
f r b = foo r  b-- non-baked-in, as you put

foo = getFld :: (r { foo :: Bool } ) = r - Bool

So the type you give would be inferred for function f.

At the use site for f (say applied to record type Bar).
We need:

instance (t ~ Bool) = Has Bar foo t where ...

So generate that on-the-fly.


If the program declares a separate function foo,
then we have 'vanilla' name clash, just like double-declaring any name.
(Just like a H98 record with field foo, then declaring a function foo.)


Or is the potential difficulty something like this:

+ function f is defined as above in a module with -XPolyRecordFields.
+ function f is exported/imported.
+ the importing module also uses -XPolyRecordFields.
+ now in the importing module we try to apply f to a record.
  (say type Baz, not having field foo)
+ the compiler sees the (r { foo :: Bool }) constraint from f.

The compiler tries to generate on-the-fly:

instance (t ~ Bool) = Has Baz foo t where
getFld (MkBaz { foo = foo }) = foo  -- no such field

But this could happen within a single module.
At this point, we need Adam to issue a really clear error message.


Or perhaps the importing module uses H98 records.
And it applies f to a record type Baz.
And there is a field foo type Bool in data type Baz.
Then there's a function:

foo :: Baz - Bool   -- H98 field selector

Now we _could_ generate an instance `Has Baz foo t`.
And it wouldn't clash with Mono field selector foo.

But the extension is switched off. So we'll get:

No instance `Has Baz foo t` arising from the use of `f` ...



(It's this scenario that led me to suggest in step 7
that when exporting field foo,
_don't_ export field selector function foo.)


 
 This raises the funny possibility that you might have to define a local 
type
   data Unused = U { foo :: Int }
 simply so that there *is* at least on foo field in scope.
 

No, I don't see that funny decls are needed.


AntC

 
 | -Original Message-
 | From: glasgow-haskell-users On Behalf Of AntC
 | Sent: 27 June 2013 13:37
 | 
 | 7. Implement -XPolyRecordFields, not quite per Plan.
 |This generates a poly-record field selector function:
 | 
 |x :: r {x :: t} = r - t-- Has r x t = ...
 |x = getFld
 | 
 | And means that H98 syntax still works:
 | 
 |x e -- we must know e's type to pick which instance
 | 
 | But note that it must generate only one definition
 | for the whole module, even if x is declared in multiple data types.
 | (Or in both a declared and an imported.)
 | 
 | But not per the Plan:
 | Do _not_ export the generated field selector functions.
 | (If an importing module wants field selectors,
 |  it must set the extension, and generate them for imported data
 | types.
 |  Otherwise we risk name clash on the import.
 |  This effectively blocks H98-style modules
 |  from using the 'new' record selectors, I fear.)
 | Or perhaps I mean that the importing module could choose
 | whether to bring in the field selector function??
 | Or perhaps we export/import-control the selector function
 | separately to the record and field name???
 | 



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


Re: Overloaded record fields

2013-06-28 Thread AntC
 Malcolm Wallace malcolm.wallace at me.com writes:
 
  
  With the orthogonal proposal, f is equivalent to
 f r b = foo r  b
 
 I believe Simon's point is that, if dot is special, we can infer 
the Has type above, even if the compiler is
 not currently aware of any actual record types that contain a foo 
field.

Thanks Malcolm, yes I think I do understand what Simon had in mind.
In effect .foo is a kind of literal.
It 'stands for' the String type foo :: Symbol parameter to Has.
(And that's very odd, as SPJ's SORF write-up points out, because that 
isn't an explicit parameter to getFld.)

But contrast H98 field selector functions. They're regular functions, 
nothing about them to show they're specific to a record decl. And they 
work (apart from the non-overloadability).

So all we're doing is moving to foo being an overloaded field selection 
function. And it's a regular overloaded function, which resolves through 
instance matching.


  If dot is not special, then there
 *must* be some record containing foo already in scope, ...

I think you have it the wrong way round.
Field selector function foo must be in scope.
(Or rather what I mean is that name foo must be in scope,
and it's in-scope binding must be to a field selector.)

And function foo must be in scope because there's a record in scope with 
field foo, that generated the function via -XPolyRecordFields.


 
 ..., where you can use a selector for a record that is not
 even defined yet, leads to good library separation.

You can't do that currently. So I think you're asking for something beyond 
Simon's smallest increment.

 
 Unless you require the type signature to be explicit, instead of 
inferred.

Well, I think that's reasonable to require a signature if you use a 
selector for a record that is not even defined yet. I'm not convinced 
there's a strong enough use case to try to support auto type inference. 
Simon said vanishingly rare.


 
 (For the record, I deeply dislike making dot special, so I would 
personally go for requiring the explicit
 type signature in this situation.)
 
 Regards,
 Malcolm
 





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


Re: Overloaded record fields

2013-06-27 Thread AntC
 Edward Kmett ekmett at gmail.com writes:
 
 Let me take a couple of minutes to summarize how the lens approach 
tackles the composition problem today without requiring confusing changes 
in the lexical structure of the language. 

Thank you Edward, I do find the lens approach absolutely formidable. And I 
have tried to read the (plentiful) documentation. But I haven't seen a 
really, really simple example that shows the correspondence with H98 
records and fields -- as simple as Adam's example in the wiki. (And this 
message from you doesn't achieve that either. Sorry, but tl;dr, and there 
isn't even a record decl in it.)

Does the lens approach meet SPJ's criteria of:
 * It is the smallest increment I can come up with that
   meaningfully addresses the #1 pain point (the inability to
   re-use the same field name in different records).

 * It is backward-compatible.

[I note BTW that as the Plan currently stands, the '.field' postfix 
pseudo-operator doesn't rate too high on backward-compatible.]

I do think that freeing up the name space by not auto-generating a record-
type-bound field selector will help some of the naming work-rounds in the 
lens TH.

 ...

You say:
 
  template-haskell functions for lens try to tackle the SORF/DORF-like 
aspects. These are what Greg Weber was referring to in that earlier email. 
 

errm I didn't see an email from Greg(?)

AntC


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


Re: Overloaded record fields

2013-06-27 Thread AntC
 Adam Gundry adam.gundry at strath.ac.uk writes:

 I've started to document the plan on the GHC wiki:
 
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Pla
n
 

Thank you Adam, (Simon)

I like the approach for Representation hiding. (That was something I was 
particularly trying to preserve out of H98 records.)

At first I was worried this would involve 'scoped' instances -- which 
seems a wild departure.

But I see in the 'Multiple modules' section that you're generating 
instances on-the-fly. So I agree that option (2) looks best.

As I understand it, this means that the extensions switched on in the 
importing module is all we have to worry about, not what extensions 
applied where the data type is declared.

So for backward compatibility, I can import historic Library L ( R(x) ) 
which knows nothing about the new stuff. And in my module (with the 
extension on) declare data type T with field x, and not have a clash of 
field names.

Sweet!





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


Re: Overloaded record fields

2013-06-27 Thread AntC
 
 ... the orthogonality is also an important benefit.
  It could allow people like Edward and others who dislike ... 
  to still use ...
 

Folks, I'm keenly aware that GSoC has a limited timespan; and that there 
has already been much heat generated on the records debate.

Perhaps we could concentrate on giving Adam a 'plan of attack', and help 
resolving any difficulties he runs into. I suggest:

1. We postpone trying to use postfix dot:
   It's controversial.
   The syntax looks weird whichever way you cut it.
   It's sugar, whereas we'd rather get going on functionality.
   (This does mean I'm suggesting 'parking' Adam's/Simon's syntax, too.)

2. Implement class Has with method getFld, as per Plan.

3. Implement the Record field constraints new syntax, per Plan.

4. Implicitly generate Has instances for record decls, per Plan.
   Including generating for imported records, 
   even if they weren't declared with the extension.
   (Option (2) on-the-fly.)

5. Implement Record update, per Plan.

6. Support an extension to suppress generating field selector functions.
   This frees the namespace.
   (This is -XNoMonoRecordFields in the Plan,
but Simon M said he didn't like the 'Mono' in that name.)
   Then lenses could do stuff (via TH?) with the name.

   [Those who've followed so far, will notice that
I've not yet offered a way to select fields.
Except with explicit getFld method.
So this 'extension' is actually 'do nothing'.]

7. Implement -XPolyRecordFields, not quite per Plan.
   This generates a poly-record field selector function:

   x :: r {x :: t} = r - t-- Has r x t = ...
   x = getFld

And means that H98 syntax still works:

   x e -- we must know e's type to pick which instance

But note that it must generate only one definition
for the whole module, even if x is declared in multiple data types.
(Or in both a declared and an imported.)

But not per the Plan:
Do _not_ export the generated field selector functions.
(If an importing module wants field selectors,
 it must set the extension, and generate them for imported data types.
 Otherwise we risk name clash on the import.
 This effectively blocks H98-style modules
 from using the 'new' record selectors, I fear.)
Or perhaps I mean that the importing module could choose
whether to bring in the field selector function??
Or perhaps we export/import-control the selector function
separately to the record and field name???

Taking 6. and 7. together means that for the same record decl:
* one importing module could access it as a lens
* another could use field selector functions

8. (If GSoC hasn't expired yet!)
   Implement ‑XDotPostfixFuncApply as an orthogonal extension ;-).

AntC




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


Re: Overloaded record fields

2013-06-26 Thread AntC
 Mateusz Kowalczyk fuuzetsu at fuuzetsu.co.uk writes:
 
 
 On 24/06/13 11:04, Roman Cheplyaka wrote:
  * Mateusz Kowalczyk fuuzetsu at fuuzetsu.co.uk [2013-06-24
  10:47:09+0100]
  Restricting function composition to have spaces around it will
  require changing a large amount of existing code if one is
  willing to use it.
  
  
 Sure that it's unreasonable to have them change some of their code to
 use new, cool features. I'm just questioning whether it's absolutely
 necessary to do it by forcing restrictions on what is probably the
 most commonly used operator in the whole language.
 

For my 2-penn'orth, requiring spaces around composition won't break any of 
my code: I always do put spaces.

Re use of 'infix' dots, I grew up on Russell  Whitehead's Principia 
Mathematica, Wittgenstein's Tractatus, BCPL (dots inside names), LISP's 
dotted pairs (which IIRC always have surrounding spaces), SQL's 
table.field.

I find it is Haskell that is 'odd man out'.

OTOH, there is a high cost in breaking that existing code with non-spaced 
composition, and I'm not convinced that record-field access alone is a 
sufficient benefit. (This is what SPJ would call a low power to weight 
ratio.)

What's more, the new dot syntax seems a bit weird:

A dotted right-section is allowed, so presumably the wiki example could go:

getPersonId e = e.PersonId
getPersonId   = (.PersonId)  -- eta reduce(?)

What do these terms mean/are they valid?

(.PersonId) e-- prefix application
e (.PersonId)-- postfix application??
let f = (.PersonId) in e.f   -- no Has instance for f

let fullName r = r.firstName ++   ++ r.lastName
e.fullName   -- trying to use Virtual field

So I'm thinking that this dot operator is not really an operator, neither 
is it part of the name as in module prefixes(?)

(I'll add some more thoughts to SPJ's comment.)

AntC



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


Re: Overloaded record fields

2013-06-26 Thread AntC
 Simon Peyton-Jones simonpj at microsoft.com writes:
 
 |  record projections.  I would prefer to have dot notation for a
 |  general, very tightly-binding reverse application, ...
 |  Such a general reverse application dot would
 |  allow things like string.toUpper and for me personally, it would
 |  make a Haskell OO library that I'm working on more elegant...
 
 Actually I *hadn't* considered that.   I'm sure it's been suggested 
before (there has been so much
 discussion), but I had not really thought about it in the context of our 
very modest proposal.

Thanks Simon, 

I'd better start by saying that I'm very keen for Adam to get going on 
this and produce something/anything better than H98's record fields. So I 
fully understand you're trying to make this a minimal proposal.

At risk of I told you so dot as postfix apply is exactly what I had in 
mind for my record proposals (DORF and TPDORF on the wiki):

- Since H98 field selectors are just functions we could leave them as is
  (leave the selector as Mono/specific to a data type)
- make the new OverloadedRecordFields also just functions
  (via the Has instance
   -- in effect this is PolyRecordFields per the wiki Plan.)
- make Virtual record fields just functions
  (don't need a Has instance, and don't get into trouble with update)
- (then toUpper could seem like a record field kinda thing)

All of them could use the dot notation syntax. (As tight-binding reverse 
function apply.)

person.lastName.toUpper-- == toUpper (lastName person)

So, as you say:
 
 It also allows you to use record field names in prefix position, just as 
now, which is a good thing.  
 
 In fact, your observation allows us to regard our proposal as consisting 
of two entirely orthogonal parts
   * Generalise the type of record field selectors
   * Introduce period as reverse function application
 

Exactly! (I did tell you so: 
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFi
elds/DotPostfix -- billed as optional syntactic sugar)
So make those two orthogonal extensions. 

For people who really don't like breaking their existing code that uses 
dot as composition in tight-binding contexts (and they were vociferous), 
they simply don't switch on the ‑XDotPostfixFuncApply extension, and they 
can still get the benefits of OverloadedRecordFields.



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


Re: Overloaded record fields

2013-06-26 Thread AntC
 
 person.lastName.toUpper-- == toUpper (lastName person)
 

Oops! that should be one of:

  person.lastName.head.toUpper

  person.lastName.(map toUpper)




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


Re: Repeated variables in type family instances - UndecidableInstances

2013-06-23 Thread AntC
 Richard Eisenberg eir at cis.upenn.edu writes:
 
 ... The plan of action is to use the check labeled (B)
 on the wiki page. This check does *not* ban all nonlinear type families.

Thanks Richard, great! Then the focus of attention moves to infinite types.

I don't think anybody intentionally wants infinite types,
so UndecidableInstances ought to be switched off,
to catch unintended instances.

But often there's a need for one or two instances to break the coverage 
conditions. (For example one of Oleg's standard techniques is to introduce 
a 'helper class' that has the same parameters as the based-on class, plus 
some extra parameter that drives instance selection, and is computed from 
the types of the arguments. It's not easy to see at this stage how that 
technique will translate into 'closed type families'.)

The trouble with the UndecidableInstances flag is that it's a very blunt 
instrument module-wide. A 'nice to have' would be to make it finer-grained:
- set Undecidableness on a per-instance or per-family basis.
- or even: validate that the RHS of this instance uses a decidable family
   but allow the RHS to break cover compared to LHS

(OK, I know that for a 'decidable' family there could be instances 
declared in other modules that get compiled with a different flag setting. 
But with 'closed type families', that can't happen, right?) 

AntC



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


Re: Repeated variables in type family instances

2013-06-22 Thread AntC
 Richard Eisenberg eir at cis.upenn.edu writes:
 
 And, in response to your closing paragraph, having type-level equality 
is the prime motivator for a lot of
 this work, so we will indeed have it!
 

Thank you Richard, I'll take comfort in that.

I'd beware this though: the Nonlinearity wikipage says a medium-intensity 
search did not find any uses of nonlinear ... family instances in existing 
code, ...

That doesn't surprise me, but I wouldn't put much weight on it. The main 
purpose of repeated tyvars in a (class) instance is so that you can have 
a 'wider' overlapping instance with distinct tyvars (and a non-congruent 
result). Since family instances don't currently support non-congruent 
overlap, I guess there would be a pent-up demand to translate class 
instances to (branched?) family instances with repeated tyvars. 

Here's two example instance from HList that mirror your two instances for 
family F:

-- pattern of instance F x x
class TypeEq a b c| a b - c
instance TypeEq x x HTrue
instance (c ~ HFalse) = TypeEq x y c

-- pattern of instance F [x] x -- actually F x (HCons x ...)
class Has e l-- constraint
instance Has e (HCons e l')
instance (Has e l') = Has e (HCons e' l')

I haven't, though, seen those two patterns appearing as instances of the 
same class.

And given that those patterns are to be allowed only within branched 
instances, the 'cleaned up syntax' makes sense -- I'm glad I suggested it! 
(see 
http://hackage.haskell.org/trac/ghc/wiki/NewAxioms/DiscussionPage#Suggestio
ns, under 'Idiom of a total function' ;-)



It still seems mildly 'unfair' to ban repeated tyvars when really the 
cause of the problem is infinite types. I take you to be saying that as 
soon as we allow UndecidableInstances, it's just too hard to guard against 
infinite types appearing from chains of instances, possibly in 'distant' 
imports or recursive module references.

So I understand it's not worth sacrificing type safety.

AntC



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


Re: Repeated variables in type family instances

2013-06-20 Thread AntC
 Richard Eisenberg eir at cis.upenn.edu writes:

Hi Richard, I was hoping one of the type/class/family luminaries would 
pick this up, but I'll make a crack at moving it along.

  
 It’s come to my attention that there is a tiny lurking potential hole in 
 GHC’s type safety around type families in the presence of 
 UndecidableInstances. ...

Hmm. Several things seem 'fishy' in your examples. I'll take the second 
one first:

  type family G
  type family G = [G]
  
 This declarations are all valid in GHC 7.6.3.

G is 0-adic, so only one instance is allowed, so it should be like a 
simple type synonym. What about:

type G2 = [G2]

 ghc rejects Cycle in type synonym declarations

But I guess ghc doesn't want to make a special case of 0-adic type 
functions. Really that G instance is no different to:

type instance F Int Bool = [F Int Bool]

G's instance is degenerate because I can't declare a term of type G:

g :: G
g = undefined

ghc says Occurs check: cannot construct the infinite type: uf0 = [uf0]

This isn't unusual in the borderlands of UndecidableInstances: you can 
declare an instance but never use it.

Now to your main example:
  
  type family F a b
  type instance F x x = Int
  type instance F [x] x = Bool
  

I plain disagree that these are overlapping. That code compiles OK with 
OverlappingInstances switched off (at ghc 7.6.1). What's more, I can 
access both instances:

*Main :t undefined :: F Int Int
undefined :: F Int Int :: Int
*Main :t undefined :: F [Int] Int
undefined :: F [Int] Int :: Bool

For them to overlap would require the two arguments to be equal in the 
second instance. In other words: [x] ~ x

Let's try to do that with a class instance:

class F2 a b
instance ([x] ~ x) = F2 [x] x

ghc rejects Couldn't match type `x' with `[x]'


So you haven't yet convinced me that there's anything that needs 'fixing'. 
Especially if you're proposing a breaking change.

I make heavy use of repeated type vars in class instances (in combination 
with an overlapped instance with distinct type vars). I have been waiting 
patiently for overlapping instances to appear with type funs, so I can 
make my code easier to read (more functional ;-). 

I guess the key thing I'm looking for is a type-level test for type 
equality -- which needs repeated type vars(?) 


Anthony





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


Re: Kindness of strangers (or strangeness of Kinds)

2012-06-12 Thread AntC
Edward Kmett ekmett at gmail.com writes:

 On Mon, Jun 11, 2012 at 9:58 PM, AntC anthony_clayden at clear.net.nz 
wrote:

 [snip ...]

 Could we have :k (-) :: OpenKind - * - *  -- why not?
 
 I don't quite understand why you would want arbitrary kinded arguments, but 
only in negative position. 


Thanks Edward, oops I've used the wrong terminology, sorry for the confusion. 
I didn't mean OpenKind but AnyKind. I put that only in a negative position 
more to sharpen the question, but also because I assumed the result from (-) 
would have to be grounded in Kind *; and then at least one of its arguments 
would also have to be grounded in Kind *.


I think perhaps(?) more PolyKindness is on the horizon: 
http://hackage.haskell.org/trac/ghc/wiki/GhcKinds  (section on GADKs, and sub-
pages on KindPolymorphism and ExplicitTypeApplication). I guess GHC is getting 
there by small steps, and doesn't yet have powerful enough Kind refinement nor 
Kind equality constraints, nor interleaving of Type and Kind inference.



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


Re: Kindness of strangers (or strangeness of Kinds)

2012-06-11 Thread AntC
Simon Peyton-Jones simonpj at microsoft.com writes:

 
 There is a little, ill-documented, sub-kind hierarchy in GHC.  I'm trying 
hard to get rid of it as much as
 possible, and it is much less important than it used to be. It's always been 
there, and is nothing to do with polykinds.
 
 I've extended the commentary a bit: see Types and Kinds here
 http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler
 
 The ArgKind thing has gone away following Max's recent unboxed-tuples patch, 
so we now only have OpenKind
 (described on the above pages).
 

Thank you Simon, Richard, ~d, et al (so much kindness to a stranger!)

It's not that I have a specific problem (requirement) I'm trying to solve. 
It's more that I'm trying to understand how this ladder of 
Sorts/Kinds/Types/values hangs together.

With Phantom types, we've been familiar for many years with uninhabited types, 
so why are user-defined (promoted) Kinds/Types different?

The Singletons stuff shows there are use cases for mapping from uninhabited 
types to values -- but it seems to need a lot of machinery (all those shadow 
types and values). And indeed TypeRep maps from not-necessarily-inhabited 
types to values.

Is it that we really need to implement type application in the surface 
language to get it all to come together? Then we won't need functions applying 
to dummy arguments whose only purpose is to carry a Type::Kind.

To give a tight example:

data MyNat = Z | S MyNat-- to be promoted

data ProxyNat (a :: MyNat) = ProxyNat   -- :k ProxyNat :: MyNat - *

proxyNat :: n - ProxyNat n -- rejected: Kind mis-match
proxyNat _ = ProxyNat

The parallel of that with phantom types (and a class constraint for MyNat) 
seems unproblematic -- albeit with Kind *.

Could we have :k (-) :: OpenKind - * - *  -- why not?


AntC


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


Re: Kindness of strangers (or strangeness of Kinds)

2012-06-07 Thread AntC
José Pedro Magalhães jpm at cs.uu.nl writes:

 On Thu, Jun 7, 2012 at 2:46 AM, AntC anthony_clayden at clear.net.nz 
wrote:
 
 What does the `ArgKind' message mean?
 
 `ArgKind` and `OpenKind` is what previously was called `?` and `??` (or the 
otherway around; I can't remember). 
http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/TypeType#Kindsubty
ping

Thanks Pedro, I'm trying to understand what's changing and why. (And I'd 
better repeat that I'm looking at 7.4.1, not HEAD; and SPJ's being perfectly 
clear that the promoted Kind stuff is not yet officially approved for prime 
time):

GHC 7.2.1 :k (-) :: ?? - ? - *

GHC 7.4.1 :k (-) :: * - * - *

At first sight (-) is becoming less polyKinded. Is the eventual aim to be:

GHC 7.6+ :k (-) :: AnyKind1 - AnyKind2 - *



You might also want to have a look at Richard and Stephanie's latest paper 
draft, about singletons, which is related to what you are trying in your 
example:http://www.cis.upenn.edu/~eir/papers/2012/singletons/paper.pdf
 

That's what I'm doing, and trying to understand the machinery behind it. The 
naieve approach I started with was how to get one-way from type to its single 
value -- I wasn't aiming for the whole singleton gig.

AntC



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


Kindness of strangers (or strangeness of Kinds)

2012-06-06 Thread AntC
I'm confused about something with promoted Kinds (using an example with Kind-
promoted Nats).

This is in GHC 7.4.1. (Apologies if this is a known bug/limitation/already 
explained somewhere -- I know 7.4.1 is relatively experimental. I have 
searched the bug tracs and discussions I could find.)

Starting with nats at type level, this works fine:

{-# OPTIONS_GHC -XTypeFamilies -XFlexibleInstances -XUndecidableInstances
-XScopedTypeVariables #-}

data ZeT;   data SuT n

class NatToIntT n
where natToIntT :: n - Int
instance NatToIntT ZeT
where natToIntT _ = 0
instance (NatToIntT n) = NatToIntT (SuT n)
where natToIntT _ = 1 + natToIntT (undefined :: n)

I converted naively to promoted Kinds:

{-# OPTIONS_GHC -XDataKinds -XPolyKinds -XKindSignatures#-}

data MyNat = Z | S Nat

class NatToIntN (n :: MyNat)
where natToIntN :: (n :: MyNat) - Int
instance NatToIntN Z
where natToIntN _ = 0
instance (NatToIntN n) = NatToIntN (S n)
where natToIntN _ = 1 + natToInt (undefined :: n)

But GHC rejects the class declaration (method's type):
Kind mis-match
 Expected kind `ArgKind', but `n' has kind `MyNat'
(Taking the Kind signature out of the method's type gives same message.)

Eh? MyNat is what I want the argument's Kind to be.


A PolyKinded version (cribbed from 'Giving Haskell a Promotion' on multi-
kinded TypeRep) also works fine:

data Proxy a = Proxy

class NatToInt (n :: MyNat)
where natToInt :: Proxy (n :: MyNat) - Int
instance NatToInt Z 
where natToInt _ = 0
instance (NatToInt n) = NatToInt (S n)
where natToInt _ = 1 + natToInt (Proxy :: Proxy n)

But this seems too Kind. I only ever want to supply Nats as arguments.

What does the `ArgKind' message mean?

(I've also seen messages with `AnyKind' -- what that?)

There's a discussion in SPJ's Records proposal last year 
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields#Shouldg
ethaveaproxyargument
Is that related?

Do I need explicit Type/Kind application for this to work?

AntC




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


Re: Kindness of strangers (or strangeness of Kinds)

2012-06-06 Thread AntC
 wagnerdm at seas.upenn.edu writes:

 
 Quoting AntC anthony_clayden at clear.net.nz:
 
  {-# OPTIONS_GHC -XDataKinds -XPolyKinds -XKindSignatures#-}
 
  data MyNat = Z | S MyNat
 
  class NatToIntN (n :: MyNat)
  where natToIntN :: (n :: MyNat) - Int
  instance NatToIntN Z
  where natToIntN _ = 0
  instance (NatToIntN n) = NatToIntN (S n)
  where natToIntN _ = 1 + natToInt (undefined :: n)
 
  But GHC rejects the class declaration (method's type):
  Kind mis-match
   Expected kind `ArgKind', but `n' has kind `MyNat'
  (Taking the Kind signature out of the method's type gives same message.)
 
 At a guess, (-) :: * - * - *, but n :: MyNat, not n :: *, so (-) n  
 is badly kinded. In comparison:
 
  data Proxy a = Proxy
 
  class NatToInt (n :: MyNat)
  where natToInt :: Proxy (n :: MyNat) - Int
  instance NatToInt Z
  where natToInt _ = 0
  instance (NatToInt n) = NatToInt (S n)
  where natToInt _ = 1 + natToInt (Proxy :: Proxy n)
 
 Here Proxy n :: *, even if n :: MyNat, so Proxy n is a fine argument  
 to hand to (-).
 
 ~d
 

Thanks for the prompt response, and yes, you're right, so says GHCi:

:k (-) :: * - * - *  -- so `ArgKind` in the message means `*'

:k Proxy :: AnyK - *   -- which answers what is `AnyKind'

So Proxy is a kind-level wormhole: forall k. k - *
Singleton types are a wormhole from types to values.

For the natToInt method, it's a shame having to insert Proxy's everywhere -- 
it takes away from the parallel to value-level equations.

Perhaps I need promoted GADT's?

Or perhaps PolyKinded (-) :: k1 - k2 - k3?

AntC


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


Re: Records in Haskell: Explicit Classy Records

2012-04-22 Thread AntC
Matthew Farkas-Dyck strake888 at gmail.com writes:

 I made another proposal for records in Haskell, meant to solve just
 the namespace problem, and no more.
 http://hackage.haskell.org/trac/ghc/wiki/Records/ExplicitClassyRecords
 

Thanks Matthew, I'm finding your wiki too sketchy to follow.

What name(s) does your proposal generate? And what type(s) do they have?

For record access, how does the compiler resolve to the right definition or 
instance from the context of use?

It seems you aren't making any proposal about record updating. So the acid 
test is how do you expect this to be treated:
 e{ x = True }
{* `e` is some arbitrary expression, possibly denoting a record type;
   `x` one of those names for which you've solved the namespace problem*}

AntC





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


Re: ANNOUNCE: GHC version 7.2.1 - {-#LANGUAGE NoTraditionalRecordSyntax#-}

2012-03-27 Thread AntC
Ian Lynagh igloo at earth.li writes:

 
 On Mon, Mar 26, 2012 at 10:47:14PM +, AntC wrote:
 
  Ticket #3356 claims that {-# LANGUAGE NoTraditionalRecordSyntax #-} was 
  implemented in 7.2.1.
  
  But GHCi v7.2.1 complains Unsupported extension: 
NoTraditionalRecordSyntax.
  
  What (if anything) actually got implemented?

 ghci -XNoTraditionalRecordSyntax does not complain of unsupported extensions 
 for me.
 ...
 Simon
 
 It was implemented in 7.4.1.
 
 Thanks
 Ian
 
Thank you Simon and Ian (and apologies for first posting to the Haskell list).

So I'll upgrade to 7.4, and play with it.

And post a ticket for the more modest idea of suppressing the (monomorphic) 
field selector function.

AntC




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


Re: ANNOUNCE: GHC version 7.2.1 - {-#LANGUAGE NoTraditionalRecordSyntax#-}

2012-03-27 Thread AntC
Simon Peyton-Jones simonpj at microsoft.com writes:

 
 ghci -XNoTraditionalRecordSyntax does not complain of unsupported extensions 
for me.

OK, it's effective in v7.4.1, as Ian says.

 
 The flag appears to just disable record construction and update syntax, and 
 record patterns, and record syntax in GADT declarations.

For the record(!) it also suppresses record syntax in ordinary data 
declarations. So it 'solves' the namespacing issue by not allowing field names 
at all.

No curly brackets, no field names nowhere! Everything has to be positional.

  It has probably never been used.
 

Yes, the pruning is _too_ radical, the tree withered away.

AntC




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


Re: Records in Haskell - updating Higher-Ranked fields

2012-03-27 Thread AntC
Gábor Lehel illissius at gmail.com writes:
 
 ..., but DORF actually requires less type system magic than
 SORF, and also already has a working prototype implementation, ...
 
 ... My main complaint against DORF is
 that having to write fieldLabel declarations for every field you want
 to use is onerous. ...
 

(Here's a possible way to reduce the need for declarations,
 for non-sharing fields; also avoid the fieldLabel new decl.)

SPJ introduced some fancy type-handling for higher-ranked fields. But still it 
only helped in accessing a H-R field, not updating it.

If we accept that updating H-R fields in liberated-namespace records is not 
possible, can we simplify the implementation? I think so. Here's what I'd call 
a well-principled work-round (not a hack, but then neither a solution).

(I'm showing it in DORF-like style, but I think it would work equally in SORF 
style with Stringy Kinds. The advantage of showing DORF is that we can try it -
- which I've done.)

You write:
data HR = HR{ objectId :: ObjectId  -- type Pun
, rev :: forall a. [a] - [a] } -- SPJ's example
 sharing (ObjectId) deriving (...)  -- new syntax
 -- this decl is not sharing `rev`, so no further code needed

 -- HR is sharing objectId, so you need a field Label in scope:
 -- probably you're already declaring newtypes/data
newtype ObjectId = ObjectId Int -- declaring a field
  deriving (Has, ... )  -- `Has` makes it a label

Field access can be polymorphic:
f :: HR - ([Bool], [Char])
f r = (r.rev [True], r.rev hello)

Record update looks like:
... myHR{ rev = Rev reverse } ...   -- annoying pun
But perhaps we could support sugar for it:
... myHR{ Rev reverse } ... -- fewer keystrokes!

The HR decl desugars to:
newtype Rev = Rev (forall a. [a] - [a])-- newtype punning
data HR = HR{ objectId :: ObjectId, rev :: Rev }
rev :: HR - (forall a. [a] - [a]) -- monotype field selector
rev r = let (Rev fn) = get r (undefined :: Rev) in fn
instance Has HR Revwhere
get HR{ rev } _ = rev   -- have to wrap the fn
set (Rev fn) HR{ .. } = HR{ rev = (Rev fn) }
type instance FieldTy HR Rev = Rev  -- have to wrap this
-- else update don't work

So I've simplified `Has` to two type arguments (like the more naieve form SPJ 
considers then rejects). And used the field's type itself as the index (so 
that we're punning on the field name):
class Has r fld   where
get :: r - fld - FieldTy r fld
set :: fld - r - SetTy r fld  -- for type change update

For the record type's `sharing` fields we desugar to:
instance Has HR ObjectId   where
get HR{ objectId } _ = objectId -- yeah dull, dull
set x HR{ .. }   = HR{ objectId = x, .. }

and the `deriving (Has)` on the newtype or data desugars to:
objectId :: {Has r ObjectId} = r - ObjectId   -- overloaded record 
objectId r = get r (undefined :: ObjectId)  -- selector
type instance FieldTy r ObjectId = ObjectId -- not parametric

AntC


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


Re: ANNOUNCE: GHC version 7.2.1 - {-# LANGUAGE NoTraditionalRecordSyntax #-}

2012-03-26 Thread AntC
 
Ian Lynagh igloo at earth.li writes:
 
=
 The (Interactive) Glasgow Haskell Compiler -- version 7.2.1
=
 
Ticket #3356 claims that {-# LANGUAGE NoTraditionalRecordSyntax #-} was 
implemented in 7.2.1.

But GHCi v7.2.1 complains Unsupported extension: NoTraditionalRecordSyntax.

What (if anything) actually got implemented?

Is/was the plan to be able to selectively 'prune' bits of record syntax? or 
just to completely banish anything with curly brackets {and their contents} 
from patterns, expressions and data declarations?

I ask because I'd like to raise a ticket for 
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
/NoMonoRecordFields -- that is, to enable declaring within the same module 
multiple record types with the same field name.

Of course it will also help when declaring the same field name in different 
(but imported) modules.

Avoiding generating the (monomorphic) field selector function is a modest step 
towards freeing up the namespace, without in any way pre-judging how 
the 'narrow namespace issue' might get addressed.

AntC




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


Re: Records in Haskell

2012-03-08 Thread AntC
 
 On Fri, Mar 02, 2012 at 01:04:13AM +, AntC wrote:
  
  Let me explain better what I mean by two private namespaces, then we'll 
   try to understand how your proposal goes ...
 

Folks, it has been very difficult keeping up with all the twists and turns of 
this thread.

So here's a summary of my proposal, by popular demand, 
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
#ThumbnailSketch

Reminder about this approach:
 * It requires no new semantics from Haskell (beyond ghc v7.2 extensions).
 * Therefore a prototype can be developed,
   and it has! you can download and see for yourself.
 * The syntax for record updates is the same as it is today.
   (Although the semantics is polymorphic, not monomorphic.)
 * The syntax for data declarations is the same as it is today.
 * The syntax for field selection is the same as it is today.
   (But polymorphic for any record with a field of that name.)
 * There is a dot notation syntax possible for field selection,
   (strictly optional, sugar only).
 * It does support type-changing update to records,
   for parametric polymorphic fields and records.

But:
 * This approach does not have a solution for updating fields of
   higher-rank types.
   (In that respect it is like SORF. This is the remaining problem.
And I suspect that any solution for SORF will equally work for DORF.)

There were some criticisms about how much boilerplate this approach would 
need. There are some ideas/suggestions to improve that. In particular 
see Option Three: Mixed In-situ and Declared ORF further down the page from 
the Thumbnail Sketch.

Constructive feedback welcome.

AntC




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


Re: Records in Haskell: Type-Indexed Records (another proposal)

2012-03-06 Thread AntC
Matthew Farkas-Dyck strake888 at gmail.com writes:

 
  I think you don't want all those type vars in your record decls -- but only
  vars for the mutatable types, like this:
 
type R c = { X ::. Int, Y::. String, Z ::. c, ... }
 
  Then you don't need a Quasifunctor instance for every field, only the
  mutatable ones.
 
 Yes, I know. That is just a very general example.
 
  Oh, and how do you deal with multiple record constructors as in H98:
 data T a = T1 { x :: a, y :: Bool }
  | T2 { x :: a }
 
 Not sure what you mean. With an argument of such a multiconstructed
 type, I would do as ever in Haskell: pattern-match.

So please show what record declarations look like. And how they get turned 
into Has instances. Your example decl on the wiki for R a b c is not valid 
Haskell. What's more the wiki hss it as a `type`. Did you mean a `data`? I'm 
confused.

 
  You don't give full details for your Has instances, but presumably you'd do
  the same equality constraint style as SORF and DORF.
 
 I assume you mean
 instance (v~a) = Has k v (R a) where ...
 
 I'm not sure why we need this, but I assume that we do, since it was
 written by SPJ, so yes.
 

Matthew, you really, really need to understand why SPJ put it that way, if you 
want your proposal to be taken seriously. He wasn't just making it up.

  You don't show how you'd do record update.
 
 Yep. It's on the wiki.
 qfmap X f r is r mutated by f at X
 

So do you mean this is what developers put in the code?

  what is the type for:
  r{ X = True }
  That is: update record r, set its X field to True.
 
 This is written as
 qfmap X (const True) (r :: r) :: Quasifunctor X a Bool r s = s;
 

You mean this is what to put in the code?

DORF is getting beaten up for the amount of boilerplate the programmer is 
expected to add (for fieldLabels, etc.) I can't compare apples with apples for 
your proposal, because I can't see what the code looks like that would appear 
in the program.

So far (apart from Quasifunctor) all I can see is that you're varying the 
sugar, without adding anything to the semantics -- except you've not given the 
surface syntax, so I'm only guessing.


AntC


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


Re: Why I (Don't!) Want Global Field Names (By Default)

2012-03-05 Thread AntC
Gershom Bazerman gershomb at gmail.com writes:

 
 ... I want to put forward
 at least one strong motivation for global field names (aka
 SORF-style) rather than locally declared field names as a default.

Hi Gershom,

One of the things that's surprised me contributing to this thread is not just 
that different people rate different features with different priority (that's 
common in requirements analysis, to try to 'weight' each objective); but that 
what some people think is absolutely critical others think is absolutely to be 
avoided. (The Best example of that is the furore about dot notation.) 

So you're not going to expect me to agree with you.

A couple of very strange things I noticed about your expectations for software 
development, so I'm happy to make clear the context I'm expecting:

* Yes, I expect you to pull in the entire namespace for [the] database
  at once. That is: in a large-scale database-oriented application,
  you would declare **all** your field labels (aka data dictionary)
  in one module, and import that into every sub-module.
  That's been standard practice in all the software shops I've worked in
  since around 1984 (System/38).
  That's exactly what Chris Done's example did, which started my thinking
  around what became DORF.
  I am, frankly, astonished anyone would contemplate any other approach
  in this day and age. Because ...

* As you say, tracing all the dependencies from code mods is hard work.
  Developers are very poor at it. Computers are superb.
  I expect you to run a nightly build, why not make it easy for yourself?
  http://www.joelonsoftware.com/articles/fog23.html
  http://www.joelonsoftware.com/articles/fog43.html
  Those articles date from over a decade ago!
  Software shops I've worked in have run nightly builds since around mid-90's.

  (It'd be interesting to hear from the ghc dev team:
   do they run a nightly build?
   Although ghc is not a database-intensive application.)

And what on earth sort of hardware are you running that your builds are time 
consuming? This is just not an issue in 2012. I expect large-scale 
applications with (say) hundreds of tables, thousands of fields, 100k's LOC to 
rebuild in a few hours.


So to my substantive answer:
* The realistic situation in modern software engineering is that you assemble
  your application out of libraries/packages.
* You have no control over the naming used in them.
* What's worse, developers are so used to strong namespacing controls,
  that they often use generic names that are likely to appear elsewhere.
  (And especially if it's in a technical domain with well-agreed jargon.)
* So you're highly likely to get clashes 'by accident'.
* Haskell's module/namespacing controls are perfectly adequate to manage this.
* And OO, as a technique insists on namespace control,
  to implement encapsulation/representation-hiding.

* In database-oriented applications, re-using the same name on different tables
  is deliberate and intentional (_not_ by accident).
* H98 is simply awful for this. DORF addresses that issue.
* That said, nothing in DORF stops you creating global names:
  simply export/import them everywhere unqualified.
  See: that wasn't too painful, was it?

So our point of difference comes down to: what behaviour By Default.
* DORF expects it's more likely you'll want namespace control.
  And makes it hardly more difficult to be global.
  And uses module-based namespace control that is already industry-standard,
  viz: Haskell 98's approach.

* SORF 'imposes' global everywhere,
  And makes it possible but awkward to control name scope.

My litmus test for your approach (as for Ian's):
* My record has fields `x`, `y`, and `z`:
  - `x` is to be gettable and settable
  - `y` is to be gettable but not settable
  - `z` is to be hidden and unguessable

Please explain how your PrivateLabel approach handles those. It's not a case 
of whether it's possible, but rather how awkward.

AntC




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


Re: Why I Want Global Field Names (By Default)

2012-03-05 Thread AntC
Gershom Bazerman gershomb at gmail.com writes:

 

Gershom, an implementation question for your proposed approach to 
representation-hiding:

(It's always easy to wave away awkwardness if you don't show the full 
mechanism. Please write up your proposal on the wiki to the same level of 
detail as SORF -- at least!.)

 However, we can do one better, and recover DORF and SORF behavior at
 once!
 
     class Label a
 
     class Label f = Has (r :: *) (f :: *) (t :: *) where
 
    get :: r - t
 
    instance Label (a :: String)
 

SORF is not proposing any change to data decls syntax, or the namespacing 
around field selector functions. How do you get from the data decl to the Has 
instance? (So that the program can get/set within its private module.)

Specifically, with:
 
    data MyPrivateLabel
 
    instance Label MyPrivateLabel
 

How to get a data decl to generate a Has instance for MyPrivateLabel, and 
avoid generating a Has instance for the String Kind?

How (within the private module) to desugar a call to get (or dot notation) to 
use MyPrivateLabel?

And record update?

(Remember that unlike DORF, SORF's field access is syntax-directed: it 
desugars dot notation to a hard-coded String Kind for the field. There's no 
clear proposal for record update as yet)

 ...  If everyone finds this agreeable (and I can
 imagine no reason they wouldn't!) ...

That's a misleading remark: you're asking people to agree to a half-baked and 
sketchy proposal.

I do not find this agreeable, and I think I've put forward heaps of reasons 
to disagree.

I expect you to:
* explain what changes you're proposing to existing syntax
* detail how to desugar that syntax to available Haskell
* detail the existing syntax you're going to desugar differently
* ideally build a prototype to prove it
* demonstrate in the prototype how the namespace control works

Then we can hold the beauty pageant.

(Oh yes: and explain what you'd have instead of dot notation, so that we can 
fire up another syntax debate ;-)

AntC



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


Re: Records in Haskell: Type-Indexed Records (another proposal)

2012-03-03 Thread AntC
Matthew Farkas-Dyck strake888 at gmail.com writes:

 
 Hello all.
 
 I wrote a new proposal for the Haskell record system. It can be found
 at http://hackage.haskell.org/trac/ghc/wiki/Records/TypeIndexedRecords
 
 Records are indexed by arbitrary Haskell types. Scope is controlled as
 scope of key types. No fieldLabel declarations needed (as in DORF).
 
 Cheers,
 strake
 

Thanks Matthew,

It's good to explore the design space.

Apart from the Quasifunctor bit, I think you'll find your proposal is a rather 
cut-down version of DORF, just using different syntactic sugar. (Oh, and with 
the arguments to Has in a different order, just to be confusing.)

You do have the equivalent of fieldLabel decls. Those are all your type 
indexes: data X = X, etc.

And you suggest defining
x = X

Which is equivalent to DORF mapping from field name `x` to phantom type 
Proxy_x, (but DORF keeps `x` as a field selector function, similar to H98).

To make `x` a selector function instead, you'd go:
x = (.) X   -- or probably x = get X, see below
Which is exactly the same as DORF (after adjusting for the different order of 
arguments).

And presumably instead of X you'd want a LongandMeaningfulLabel?

And if your 
data Customer_id = Customer_id
was always an Int field, wouldn't it help the reader and the compiler to say 
that? (That's the main extra part in fieldLabels.)

I think you don't want all those type vars in your record decls -- but only 
vars for the mutatable types, like this:

  type R c = { X ::. Int, Y::. String, Z ::. c, ... }

Then you don't need a Quasifunctor instance for every field, only the 
mutatable ones.

Oh, and how do you deal with multiple record constructors as in H98:
   data T a = T1 { x :: a, y :: Bool }
| T2 { x :: a }

It wouldn't work to have a different record type for each constructor, 'cos 
you'd turn functions that use them from mono to polymorphic (overloaded -- 
needing a class and instances).

You don't give full details for your Has instances, but presumably you'd do 
the same equality constraint style as SORF and DORF.

I think you still need method get and sugar to turn the dot notation into a 
call to get. Having method (.) will usurp altogether dot as function 
composition -- you'll make a lot of enemies! And we need tight binding for dot 
notation, so we might as well treat it as special syntax.

You don't show how you'd do record update. The litmus test is what is the type 
for:
r{ X = True }
That is: update record r, set its X field to True.

AntC




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


Re: Records in Haskell

2012-03-02 Thread AntC
Isaac Dupree ml at isaac.cedarswampstudios.org writes:

...
  So under your proposal, a malicious client could guess at the fieldnames in
  your abstraction, then create their own record with those fieldnames as
  SharedFields, and then be able to update your precious hidden record type.
 
 Show me how a malicious client could do that.  Under DORF plus my 
 mini-proposal,
 
 module Abstraction (AbstractData) where
...
 fieldLabel field1 --however it goes
 [code]

Isaac here's a suggestion: please write up your proposal on a wiki.

Don't expect that your readers will have bothered to read any of your posts, 
not even those a few back in the thread.

Don't expect they'll have read the DORF proposal, or the SORF, or TDNR, nor 
even the front page of the Records wiki.

Don't expect anybody will believe your claims unless you produce a prototype 
showing how you translate your code into legal Haskell.

Don't expect anybody will believe your prototype unless it has meaningful 
field names and is illustrating a realistic business application.

Once people look at your code or wiki, don't expect they'll get your syntax 
right: you'll have to explain that from scratch.

Don't expect they'll even bother to get this right:
 fieldLabel field1 --however it goes

Don't expect they'll understand the difference between a polymorphic record 
system vs. the narrow namespacing issue - in fact expect them to make all 
sorts of suggestions for polymorphic record systems.

Don't expect they'll try running the prototype code you laboured so hard to 
get working.

Do expect to get a heap of requests for clarifications, which you also put up 
on to the wiki so that it grows and grows -- even to explain things which you 
thought were pretty obvious.

Do expect to explain the standard Haskell behaviour that you have not changed. 
It's not enough to say This follows standard Haskell behaviour. Do expect to 
find your wiki page growing and growing.

Do expect to get a load of posts starting I haven't followed everything, ... 
or It's a while since I 'tuned out' of the Records thread, ... and wanting 
you to explain all the bits they could read for themselves on the wiki.

Then expect they'll pick a few words out of your summary and lambast you for 
it, even though you politely requested they read the wiki to get the full 
story (and which they clearly did not do).

Throughout all this do expect to remain patient, civil and polite.

Do not expect to have a social life or get much sleep. Do expect your wife to 
ask who you're writing to, and why.


AntC



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


Re: Records in Haskell

2012-03-02 Thread AntC
Gábor Lehel illissius at gmail.com writes:

 ...
 
 ... My main complaint against DORF is
 that having to write fieldLabel declarations for every field you want
 to use is onerous. If that could be solved, I don't think there are
 any others. (But even if it can't be, I still prefer DORF.)
 

Thank you Gábor, I understand that 'complaint'.

I have been trying to keep the design 'clean': either the module is totally 
DORF, or it's totally H98.

But I've also tried to conform to H98 style where possible. So:
* DORF field selectors are just functions, like H98 field selector functions.
* dot syntax is just reverse apply, so could be used for H98 selectors
* pattern syntax still works, and explicit record constructor syntax
   (relying on DisambiguateRecordFields)
* record update syntax is the same (but with a different desugarring)
* record decl syntax is the same
  (but desugars to a Has instance, instead of a function)

There have been several suggestions amongst the threads to mix H98-style 
fields with DORF-style records (or perhaps I mean vice-versa!):
* We'd need to change the record decl syntax to 'flag' DORF fields (somehow).
* H98 fields desugar to monomorphic field selector functions, as usual.
  So if you have more than one in scope, that's a name clash.
* DORF fields desugar to Has instances.
  (providing you've declared the fieldLabel somewhere)
  Perhaps we could take advantage of knowing it's DORF
   to pick up the field type from the fieldLabel decl?

I think you could then 'mix and match' DORF and H98 fields in your expressions 
and patterns (that was certainly part of my intention in designing DORF).

There's one difficulty I can see:
* record update would have to know which sort of field it was updating in:
r{ fld = expr }
  If `fld` is DORF, this desugars to a call to `set`.
  If H98, this code stands as is.
What about:
r{ fldH98 = expr1, fldDORF = expr2, fldH983 = expr3, fldDORF4 = expr4 }
I think:
* for DORF updates `set` can only go one field at a time,
  so it turns into a bunch of nested `set`s
  (One for fldDORF, inside one for fldDORF4.)
* for H98 it can do simultaneous, so in effect we go:
  let r' = r{ fldDORF = expr2, fldDORF4 = expr4 }   -- desugar to nested
in r'{ fldH98 = expr1, fldH983 = expr3 }

Remaining question: how do we tell a DORF field from a H98,
at the point of the record update expression?
What is the difference? Find the field selector in the environment from the 
name:
- if monomorphic, it's H98
- if overloaded, it's DORF

But! but! we don't know its type until the type inference phase.
Yet we need to desugar the syntax at the syntax phase(!)

Suggestions please!


Also an obfuscation factor: perversely, the record type and field labels might 
have been exported, but not the selector function.



AntC




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


Re: Records in Haskell

2012-03-02 Thread AntC
Isaac Dupree ml at isaac.cedarswampstudios.org writes:

 
 
  In the meantime, I had an idea (that could work with SORF or DORF) :
 
  data Foo = Foo { name :: String } deriving (SharedFields)
 
  The effect is: without that deriving, the declaration behaves just
  like H98.
 
  Thanks Isaac, hmm: that proposal would work against what DORF is trying to 
do.
 
  What you're not getting is that DORF quite intentionally helps you hide the
  field names if you don't want your client to break your abstraction.
 
  So under your proposal, a malicious client could guess at the fieldnames in
  your abstraction, then create their own record with those fieldnames as
  SharedFields, and then be able to update your precious hidden record type.
 
 Show me how a malicious client could do that.  Under DORF plus my 
 mini-proposal,
 
 module Abstraction (AbstractData) where
 data AbstractData = Something { field1 :: Int, field2 :: Int }
 ...
 --break abstraction how? let's try...
 
 module Client1 where
 import Abstraction
 data Breaker = Something { field1 :: Int } deriving (SharedFields)
 -- compile fails because there are no field-labels in scope

Correct that the fieldLabel is not in scope, so that compile will fail; but 
what price did you pay?

Hint: what did you import with `Abstraction`?
Answer: you did not import `field1` selector function, nor the mechanism 
behind it.

So in module Client1 you can't access the `field1` content of a record type 
AbstractData. 

OK, that's sometimes something you want: to be able to pass around records of 
a specific type without allowing the client to look inside them at all.

But I was talking about the more common requirement for encapsulation. I want 
to control access to my record type: the client can read (certain) fields, but 
not update them. Other fields I don't want the client to even know about. 
(You've achieved the last part with your Client1, for all of the fields.)

(FYI: that's how wiki pages turn out so long; specifying exactly all the ins 
and outs at that sort of subtle detail.)

AntC




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


Re: Records in Haskell

2012-03-02 Thread AntC
AntC anthony_clayden at clear.net.nz writes:

 
 Gábor Lehel illissius at gmail.com writes:
 
  ...
  
  ... My main complaint against DORF is
  that having to write fieldLabel declarations for every field you want
  to use is onerous. If that could be solved, I don't think there are
  any others. (But even if it can't be, I still prefer DORF.)
  
 
 Thank you Gábor, I understand that 'complaint'.
 
 I have been trying to keep the design 'clean': either the module is totally 
 DORF, or it's totally H98.
 
 ...
 There have been several suggestions amongst the threads to mix H98-style 
 fields with DORF-style records (or perhaps I mean vice-versa!):
 * We'd need to change the record decl syntax to 'flag' DORF fields (somehow).
 ...
 There's one difficulty I can see:
 ...
 
 Suggestions please!
 

Wow! well thank you for all that hard thought going into my question.

I've put up a tweak to the proposal as Option Three: Mixed In-situ and 
Declared ORF.

This does _not_ re-introduce H98 style fields, but does simulate them in a way 
that fits better with DORF.

Do I dub this MIDORF? How will the cat with the hariballs pronounce it ;-)?

[Oh, and sorry Isaac: the word count on the wiki has gone up some more.]

AntC



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


Re: Records in Haskell

2012-03-01 Thread AntC
J. Garrett Morris jgmorris at cs.pdx.edu writes:

 
 On Wed, Feb 29, 2012 at 11:05 PM, AntC anthony_clayden at clear.net.nz 
wrote:
  I repeat: nobody is using a type-level string. You (or someone) is
  making it up.
 
 It isn't clear where that idea came from.
 
 On Mon, Jan 2, 2012 at 4:38 AM, Simon Peyton-Jones
 simonpj at microsoft.com wrote:
  It seems to me that there's only one essential missing language feature,
  which is appropriately-kinded type-level strings (and, ideally, the ability
  to reflect these strings back down to the value level).
 
  * Provide type-level string literals, so that “foo” :: String
 
 Huh.

Thank you Garrett, I feel suitably chided. So the 'culprit' is 'your man 
himself'.

 
 You may want to call your type-level-things-that-identify-fields
 strings, labels, fieldLabels, or rumbledethumps, but surely that's not
 the point of interest here?
 
  /g
 

Ah, but there _is_ a point of interest: under DORF I _must_ call my type-level-
things-etc: **types** (or perhaps proxy **types**),

Because they are only and exactly **types**.

And because they are exactly **types** they come under usual namespace control.

SORF's whadyoumaycalls are at the Kind level. (I'm not opposed to them because 
they're new-fangled, I'm opposed because I can't control the namespace.)

AntC



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


Re: Records in Haskell

2012-03-01 Thread AntC
J. Garrett Morris jgmorris at cs.pdx.edu writes:

 On Wed, Feb 29, 2012 at 11:58 PM, AntC anthony_clayden at clear.net.nz 
wrote:
  SORF's whadyoumaycalls are at the Kind level. (I'm not opposed to them
  because they're new-fangled, I'm opposed because I can't control the
  namespace.)
 
 Nah, they have kinds, and they don't take parameters, so they're
 probably types.  Whether you prefer that foo in module A mean the same
 thing as foo in module B is entirely up to you; ...
  /g
 

It's about representation hiding:
- I don't want the importer to even know I have field foo,
- but they can use my field bar

Or perhaps:
- I don't want the importer to update field foo
- but they can read foo, and they can update bar

(This is especially to support using records to emulate OO, where we want 
abstraction/'separation of concerns'.)

If the importer (either maliciously or by accident) creates their own record 
with a foo field, I specifically _don't_ want them to try sharing my 
hidden foo.

AntC


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


Re: Records in Haskell

2012-03-01 Thread AntC
Ian Lynagh igloo at earth.li writes:

 
 On Thu, Mar 01, 2012 at 07:58:42AM +, AntC wrote:
  
  SORF's whadyoumaycalls are at the Kind level. (I'm not opposed to them 
because 
  they're new-fangled, I'm opposed because I can't control the namespace.)
 
 I haven't followed everything, so please forgive me if this is a stupid
 question, but if you implement this variant of SORF:
 
 
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields#Scopeco
ntrolbygeneralisingtheStringtypeinHas
 
 then do you get the behaviour of SORF when using field names starting
 with a lower-case letter, and DORF when they start with an upper-case
 letter?
 
 Thanks
 Ian
 

And you get In my opinion, this is ugly, since the selector can be either a 
type name or a label and the semantics are nonsame. Rather, we need scoped 
instances. [SPJ]

So if we open the gate for ugly, do we also open it for hacks and 
for unscalable?

Then we also have a solution for updating higher-ranked typed fields.

I guess this is all for decision by the implementors.

If we need to go into scoped instances, I'd be really scared -- that seems 
like a huge, far-reaching change, with all sorts of opportunity for mysterious 
compile fails and inexplicable behaviour-changing from imports.

I have some creative ideas for introducing overlapping instances; shall I run 
them up the flagpole as well?


AntC



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


Re: Records in Haskell

2012-03-01 Thread AntC
Ian Lynagh igloo at earth.li writes:

 
 On Thu, Mar 01, 2012 at 08:52:29PM +, AntC wrote:
  
  And you get In my opinion, this is ugly, ...
 
 That comment was from strake888, not SPJ?
 

Thanks Ian, you're right. Specifically, it's 'igloo's tweak to the proposal 
and 'strake888's comment. (I had erroneously thought the whole of that page 
was SPJ's, and I hadn't much re-read it since SPJ posted it.)


 Personally, in the context of Haskell (where the case of the first
 character often determines the behaviour, e.g. a pattern of Foo vs foo),
 I don't think it's too bad.
 

Hmm. Upper case in an expression always means data constructor (or qualified 
name). (You've possibly not been watching the outrage at changing the meaning 
of `.` ;-)

Also this would be ambiguous:

object.SubObject.Field.subField

-- are the `SubObject` and `Field` (private) field selectors,
-- or a qualified name for subField?
-- or perhaps SubObject.Field is a qualified private field selector?

Putting parentheses would cut out some of those interpretations, but not all 
of them??


In terms of scope control, I think (I'm guessing rather) you do get similar 
behaviour to DORF, with the added inconvenience of:
* an extra arg to Has (how does the constraint sugar cope?)
r{ field :: Int } = ...
r{ Field :: Int } = ...   -- ? does that look odd
  -- suppose I have two private namespaces
r{ Field :: Int ::: Field1 } = ... -- ??
r{ (Field ::: Field2) :: Int } = ...   -- ???
* something(?) extra in record decls:
data PublicRecord = Pub { field :: Int }
data PrivateRecord = Priv { Field :: Int }-- ?
data PrivateRecord = Priv { Field :: Int ::: Field2 } -- ??
* a need for equality constraints between Kind and Type
  (that's the ft ~ FieldT bit)
  The class decl and instances are 'punning' on tyvar `ft`
   being both a type and a Kind.
  Is that even contemplated with Kinds?
* a need for something(?) different on record update syntax:
pubRec{ field = 27 }
privRec{ Field = 92 }  -- does upper case there look odd to you?
privRec{ Field = 87 ::: Field2 }

(ugly is a mild reaction, the more I think about it.)

 
 But I think you are agreeing that (leaving aside the issue of whether
 the design is reasonable) the above variant would indeed allow the user
 to choose the behaviour of either SORF or DORF.
 

No, not the user to choose, but the implementor. We can't possibly try to 
support both approaches.

AntC





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


Re: Records in Haskell

2012-03-01 Thread AntC
AntC anthony_clayden at clear.net.nz writes:

 
 Ian Lynagh igloo at earth.li writes:
 
  
  But I think you are agreeing that (leaving aside the issue of whether
  the design is reasonable) the above variant would indeed allow the user
  to choose the behaviour of either SORF or DORF.
  
 
 No, not the user to choose, but the implementor. We can't possibly try to 
 support both approaches.
 

Sorry, I mis-interpreted your last paragraph. I think you meant:

... allow the user to choose [public or restricted namespacing] behaviour 
under either the SORF or DORF proposal.

Yes-ish (leaving aside that issue). Under SORF you hve an extra behaviour:
- use String Kinds and your label is public-everywhere and
   completely uncontrollable.
- (So someone who imports your label can't stop it getting re-exported.)
- This is unlike any other user-defined name in Haskell.

I'm not sure whether to call that extra behaviour a 'feature' (I tend more 
to 'wart'), but it's certainly another bit of conceptual overload.

I prefer DORF's sticking to conventional/well-understood H98 namespacing 
controls.


AntC






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


Re: Records in Haskell

2012-03-01 Thread AntC
Ian Lynagh igloo at earth.li writes:

 
 On Thu, Mar 01, 2012 at 11:32:27PM +, AntC wrote:
  AntC anthony_clayden at clear.net.nz writes:
  
   
   Ian Lynagh igloo at earth.li writes:
   

But I think you are agreeing that (leaving aside the issue of whether
the design is reasonable) the above variant would indeed allow the user
to choose the behaviour of either SORF or DORF.

   
   No, not the user to choose, but the implementor. We can't possibly try 
to 
   support both approaches.
   
  
  Sorry, I mis-interpreted your last paragraph. I think you meant:
  
  ... allow the user to choose [public or restricted namespacing] behaviour 
  under either the SORF or DORF proposal.
 
 Yes, exactly.
 
  Yes-ish (leaving aside that issue). Under SORF you hve an extra behaviour:
  - use String Kinds and your label is public-everywhere and
 completely uncontrollable.
  - (So someone who imports your label can't stop it getting re-exported.)
  - This is unlike any other user-defined name in Haskell.
  
  I'm not sure whether to call that extra behaviour a 'feature' (I tend more 
  to 'wart'), but it's certainly another bit of conceptual overload.
 
 Right, but other people would prefer the SORF behaviour to the DORF
 behaviour.
 

Would they? How could we know? Most of the posts here have been from people 
who don't get anywhere near to understanding the issues. There's been a 
voicifereous poster who wants to have lots of fields with the same name and 
have them each mean something different. (No, I don't understand either.)

Under DORF they could get the public-everywhere behaviour by exporting and 
importing unqualified (just like H98!).

 But note that if this was implemented, then the only difference between
 the 3 is in the desugaring. So if you desugar r.f only then you get
 SORF, r.F only then you get DORF (well, with different syntax,
 probably), and if you desugar both then you get the choice.
 
 Thanks
 Ian
 

Sorry Ian, but I've got conceptual overload. I feel I understand DORF 
behaviour not just because I designed it, but also because I can (and have!) 
prototyped it under GHC v7.2, including public-everywhere and controlled 
import/export -- see my additional attachment to the implementor's page.

With Kinds and Stringy Kinds and type-to-Kind equality constraints I feel I 
want to better understand how that affects the design space. I don't think 
that's possible yet, even in v7.4(?)

Right from the beginning of SPJ's SORF proposal, I've had a feeling that ghc 
central, having introduced the new whizzy Kinds, now wants to find a use for 
them. Surely there would be other applications for Kinds that would be clearer 
use cases than patching-up Haskell's kludgy record design?

We're focussing too narrowly on this representation-hiding issue. There are 
other important differences between SORF and DORF (which I've tried to explain 
on my comparison page on the wiki). Nothing you've said so far is being 
persuasive.

(BTW on the comparison wiki, I've put some speculations around using Kinds 
behind the scenes as an implementation for DORF -- implementor's choice. 
Because it's behind the scenes we could use a more compact/specific variety of 
Kind than String. But it's still in danger of suffering the uncontrollable 
public-everywhere issue. Could you suggest an improvement?)

AntC



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


Re: Records in Haskell

2012-03-01 Thread AntC
Ian Lynagh igloo at earth.li writes:

 
  * an extra arg to Has (how does the constraint sugar cope?)
 
 You can infer ft from the f.
 

Let me explain better what I mean by two private namespaces, then we'll try 
to understand how your proposal goes ...

  module T where
  data FieldT = Field
  data RecT = RecT{ Field :: Int }
  ...
  module U where
  data FieldU = Field
  data RecU = RecU{ Field :: Bool }
  ...
  module V where
  import T -- also consider either/both
  import U -- imports hiding (Field)
  data RecV = RecV{ Field :: String }  -- am I sharing this Field?
   -- who with?
  ...
  ... r.Field ...   -- is this valid?, if not what is?
  ... r{ Field = e }-- likewise

(Oh yeah, imports and hiding: how do I do that for these non-String-type-Kinds?
And is this allowed?:
  data NotaField = Constr Int Bool
  data AmIaRec = AmI{ Constr :: String }
  ...
  ... r.Constr ...

It's all getting very tangled trying to squeeze constructors into other roles.)


AntC


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


Re: Records in Haskell

2012-03-01 Thread AntC
Isaac Dupree ml at isaac.cedarswampstudios.org writes:

AntC (in an unrelated reply to Ian) :
 I prefer DORF's sticking to conventional/well-understood H98 namespacing
 controls.

...
 I'm not sure yet that DORF's namespacing is well-understood by 
anyone but you.

No of course I'm not saying DORF's namespacing is well-understood. I mean:

1. H98 namespacing controls are conventional and well understood.

2. DORF uses H98 controls and only them.

Re 2: Partly you'll just have to take my word for it, but mainly the 
implementors will have to prove it to themselves if DORF is ever going to see 
the light of day, so I'd be daft to claim something I didn't have good 
evidence for.

Also there's strong corroboration: there's a prototype implementation attached 
to the wiki. You can download it and compile it (one module importing the 
other), and run it and try to break the abstractions, and demonstrate sharing 
the fields that are sharable.

You can inspect the code to see if I've desugarred my syntax correctly, or 
introduced some trick. (If you see anything 'suspicious', please ask.)

In fact, doing all that would be a far better use of your time (and mine) than 
all that verbiage and word counting.

AntC


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


Re: Records in Haskell

2012-02-29 Thread AntC
Isaac Dupree ml at isaac.cedarswampstudios.org writes:

 
 In the meantime, I had an idea (that could work with SORF or DORF) :
 
 data Foo = Foo { name :: String } deriving (SharedFields)
 
 The effect is: without that deriving, the declaration behaves just 
 like H98.
 
 (For super flexibility, allow to specify which fields are shared,
 like deriving(SharedFields(name, etc, etc)) perhaps.)
 
 Is it too verbose? Or too terrible that it isn't a real class (well, 
 there's Has...)?
 
 -Isaac
 
Thanks Isaac, hmm: that proposal would work against what DORF is trying to do.

You're right about the `deriving` syntax currently being used for classes. The 
fact of re-purposing the surface syntax is really no different to introducing 
different syntax.

Apart from that, it might work for SORF -- and fall into exactly what I don't 
like about SORF, which is that it sabotages the namespace/module control that 
applies for every other user-defined name in Haskell.

What you're not getting is that DORF quite intentionally helps you hide the 
field names if you don't want your client to break your abstraction.

So under your proposal, a malicious client could guess at the fieldnames in 
your abstraction, then create their own record with those fieldnames as 
SharedFields, and then be able to update your precious hidden record type.

And guessing the fieldnames is dead easy if you've exported the field selector 
function, to allow read-only access -- or so you thought.

Under DORF, despite the client guessing the fieldnames, they can't use them at 
all if you don't export them -- because they're in a sealed-off namespace, 
just like regular Haskell.

AntC




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


Re: Records in Haskell

2012-02-29 Thread AntC
wren ng thornton wren at freegeek.org writes:

 
  That's what SORF does: the String Kind
 
  No proposal is using a _type_-level string. Barney's confused you.
 
 I was under the impression that all the working proposals were using the 
 Has class, ...

Yes, but:

 a la:
 
  someFunction :: Has name a = a - Foo
  someFunction x = ... (name x) ...
 

No! Have you read any of the proposals? Which bit of your anatomy did you use?

Note that that syntax is not valid H98. Also note that the `Has` class uses 
three arguments, and in a different sequence to what you show.

That syntax (with 3 args present) turns up in two places:
1. SPJ's SORF proposal
2. Barney Hilken's postings. Please ignore them, is all I can say.
   Neither I nor SPJ had anything to do with them.

The DORF syntax is:

  someFunction :: Has r Proxy_name t = r - t

I prefer the sugar, which is the same for SORF and DORF (SPJ invented it, I 
stole it unashamedly):

  someFunction :: r{ name :: t } = r - t

The difference between the desugarring is crucial:
- SORF desugars to a String Kind -- hence Has r name t = ...
the name in quotes represents a String Kind

- DORF desugars to a (proxy) type, not some new-fangled Kind
 Has r Proxy_name t = ...
  That is H98 (with multi-param type classes).

I propose we use the sugar, so that the implementor can decide how to, um, 
implement.

 modulo the debate about the value-level syntax for records, and modulo 
 the debate about whether Has should be exposed to users or hidden inside 
 GHC. Is this no longer the case?

Was _never_ the case, you've been paying too much attention to the wrong 
postings. Look at the wiki pages: that's why I posted it.

I repeat: nobody is using a type-level string. You (or someone) is making it 
up.

This is beginning to exasperate me. Read the wikis: can you see type-level 
string? Certainly not on the DORF pages, I'm pretty sure not on the SORF 
pages. If you find it somewhere else, tell me and I'll get it changed.

AntC



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


Re: Records in Haskell

2012-02-28 Thread AntC
Barney Hilken b.hilken at ntlworld.com writes:

 
 
  Please remember SPJ's request on the Records wiki to stick
  to the namespace issue. We're trying to make something
  better that H98's name clash. We are not trying to build
  some ideal polymorphic record system.
 
 I must admit that this attitude really gets my hackles up. 
 
 Barney.
 

So Barney, the obligation on you is clear:
- pick one of the many theoretically sound clean designs for records
- (or make up your own)
- write it up on the wiki
- show what work it would need to get there from where we are
- encourage discussion on this forum

One thing I can be pretty sure of: proposals not written up won't get 
implemented.

AntC




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


Re: Records in Haskell

2012-02-28 Thread AntC
wren ng thornton wren at freegeek.org writes:

 
 I'm not sure that I like the current proposals for how to control the 
 non/automatic-ness of polymorphism (for reasons I can spell out later, 
 if desired). But we definitely want to have something that's a bit more 
 cultured than simply making all record projectors polymorphic over records.
 

Wren, I'm not sure if you've got it straight. (It's a subtle issue.) This is 
an area where SORF differs from DORF:
- SORF can't hide the representation of a given field name
  (so a client program can 'guess' a field identifier)
  That's because SORF is driven by String Kind, which cannot be scope 
controlled.

- DORF uses (Proxy) types for (roughly) the same purpose as the String Kinds.
  But because they're types, you can control the scope, and keep the 
abstraction.


AntC


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


Re: Records in Haskell

2012-02-28 Thread AntC
wren ng thornton wren at freegeek.org writes:
 
 FWIW, this is the concern I alluded to earlier. Namely that we may want 
 to have two (or more), er, 'classes' of records--- where a field is 
 polymorphic over an individual class, but we don't want those classes to 
 merge simply because they happened to choose the same name and type for 
 the field.
 

I agree 'classes' is a misleading word for that. Isn't what you want two (or 
more) namespaces for records -- that is, for their fields?

This is the DORF approach. (Barney seems to be describing the SORF approach -- 
he's got DORF wrong.)

One of the namespaces includes Product.name; another Person.name. (So I'm 
taking a namespace as equivalent to a module.) You can have multiple records 
with a `name` field in each module (Customer, Employee, Business Contact, 
etc) -- so this is already better than H98.)

Providing you're coding in a module that imports only one of those namespaces, 
you can use `name` unqualified.

If you're coding in a module that imports both, you must use `name` qualified.

If you try to apply (Product.name customer) you'll get a type failure (no 
instance).



 I'm not sure it's a good proposal, but it seems like the only way to 
 handle this issue is to (1) introduce a new kind for 
 semantically-oriented field names,

That's what SORF does: the String Kind

 and (2) make the Has class use that 
 kind rather than a type-level string.

No proposal is using a _type_-level string. Barney's confused you.

DORF uses a type (regular importable/qualifiable/hidable) with a prefix to the 
field name:
data Proxy_name

Where you're in a module that imports both the `name`s per above, the 
desugarrer would generate Product.Proxy_name and Person.Proxy_name.

(That's all rather awkward to get right, which is why I prefer the sugar.)

 By (1), what I mean is that rather 
 than referring to the field as name, we would declare PersonalName and 
 BrandName and then use those in lieu of the string. And if we do that, 
 then (2) demands that we must somehow make explicit which one we mean, 
 should we want the `name` field to be polymorphic for some given record 
 declaration.
 

AntC



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


Re: Records in Haskell

2012-02-28 Thread AntC
Barney Hilken b.hilken at ntlworld.com writes:

 
  My objection is that I'm not sure if there is ever a case where you
  really want things to be polymorphic over all records.
 
 Well, I don't have a simple, really convincing example, but there are 
certainly things I want to play with.
 More importantly, DORF automatically attaches one class to each label, but 
this is often not what you want.

Barney, you seem to be very confused. Added to that you're mixing up DORF with 
SORF. Agreed both proposals are similar, but there are crucial differences and 
you've completely befuddled them.

In DORF (and SORF) there is only one class -- namely `Has`, with methods `get` 
and `set`.

SORF 'attaches' one Kind for each label. (I'm not sure 'attaches' is the right 
word -- perhaps 'provides' is better? It's a String Kind same as the label 
name.)
In DORF you must _declare_ a _type_ for the label. (Hence **Declared** 
Overloaded Record Fields.) Since it's declared and it's a type, it has usual 
namespace (module) control. You can declare as many as you want, providing you 
respect the namespacing.


 For example, if you have two fields firstname and lastname the 
associated classes are less useful:
 what you really want is 
 
   class (Has r firstname String, Has r lastname String) = 
HasPersonalName r
 

That example is a SORF declaration: it uses String Kinds.

The DORF equivalent would be:

  class (Has r Proxy_firstname String, Has r Proxy_lastname String) =
   HasPersonalName r
Note: familiar Haskell proxy types, _not_ new/untried String Kinds.

That Proxy stuff is a mouthful, and easy to mistype. I prefer the sugar:
  class (r{firstname, lastname :: String} ) =  ...


 so that you can define
 
  fullname :: HasPersonalName r = r - String
  fullname r = r.firstname ++   ++ r.lastname
 
 You may also want to define subclasses to express more specific conditions. 
In general, the compiler
 cannot automatically deduce what is semantically important: you need to 
define it yourself. The Has
 class is the base on which you can build.

 ...

 My approach achieves the same as
 DORF (and more), but using existing language features instead of introducing 
new ones.
 
 Barney.
 

What you say there applies to SORF, not DORF. DORF deliberately uses existing 
class features and familiar type instance resolution. (Because I didn't like 
the 'experimental' Kinds in SORF, and you couldn't control their namespace.)

So what you call My approach is almost identical to DORF -- except that 
you're confusing it with SORF syntax. What you're criticising is SORF, not 
DORF.

AntC





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


Re: Records in Haskell

2012-02-28 Thread AntC
Isaac Dupree ml at isaac.cedarswampstudios.org writes:

 
 
 Darn, I misinterpreted DORF.  There was too much text and too many options.
 

Sorry! You might do better to stick to the implementor's page if you want a 
less 'option-laden' description. Also better to skip the speculative bits 
until you've got the basics clear.


 Tell me if I'm correct:
 A. Every declaration with record syntax creates Has instances for all 
 fields [1].

Correct

 B. Has, get and set may not be written by users (guessing due to 
 representation-hiding fail).

Correct: I want the implementors to have design space for the mechanics behind 
the scenes.

 C. You create functions using fieldLabel name [...]

Correct-ish: create both functions and a proxy types. It's really the type 
that drives inference, not the function.

 D. which have the magical effect of, when in scope unqualified, ...

Nothing 'magical' going on: they're ordinary functions and types, with 
ordinary import/export/hiding. And you can use them qualified if you'd rather.

 ... causing 
 data types defined with record syntax to be accessible through that 
 particular fieldLabel function (and no other way).

The fieldLabel function behaves very similar to the H98-generated function. 
The difference is with DORF it's overloaded, but H98 is monomorphic.

You can still access the fields as per H98 through pattern match (using the 
data constructor), or positionally. [Yes I know that if we were designing 
a 'true' polymorphic record system we'd ban positional access.]

 E. (When two fieldLabels of the same name are in scope unqualified, 
 declaring a record containing that name is an error.)

Correct. Just like having any other clash of names in scope (for example all 
the competing declarations of `map`). And just like those, you can use module 
qualifiers to resolve the clash.

 F. So adding an import (for some other reason for your code) that 
 happens to include a fieldLabel can make your records accidentally be 
 more visible, rather than be compile-error or no-effect.

Wrong: You cannot use a fieldLabel `name` declared in module/namespace A to 
access a record with a field `name` declared in module B. You'll get a 'no 
instance' compile fail. Same familiar rules as for any instance resolution.

This is the crucial difference compared to SORF: which can't control the scope 
of its String Kind. (Apologies that I added a speculative discussion of 
whether DORF could use String Kinds. I said that if doing so would open 
the 'back door' to the abstraction, then I'll stick with types.)

 
 I feel weird about record fields having an option that depends on 
 whether something's in scope and cannot be controlled syntactically. 
 Maybe we can fix that without making the syntax worse.
 

Absolutely agree. I designed DORF to correct that deficiency in SORF (as I saw 
it).


 G. It is possible (but rather ugly) to use dot-notation when there are 
 multiple fieldNames of the same name in scope. [2]
 

Yep, agree with the ugly.


 Hmm.  Maybe this is Haskelly as well as convenient enough.  Did I get 
 everything right?  What do you think about my concern about F?
 

Well done! Nearly everything. I hope I've allayed your concerns re F.

AntC


 [1] 
 
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
/ImplementorsView
 [2] 
 
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
/DotPostfix#UsingDotnotationamongstqualifiednames
 





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


Re: Records in Haskell

2012-02-28 Thread AntC
Barney Hilken b.hilken at ntlworld.com writes:

 
 After more pondering, I finally think I understand what the DORFistas want. 

Barney,

1) please don't personalise. I designed DORF, built a proof of concept, got it 
running, asked for feedback (got some very useful thoughts from SPJ), built a 
prototype, posted the wiki pages. I'm not a DORFista; I'm somebody who wants 
to improve the Haskell records namespace issue.

2) whether or not you think you know what some people want, you don't 
understand DORF, and you've mixed it up with SORF. You've then caused a great 
long thread of confusion.

In particular, at exactly where DORF is designed to avoid (what I see as) a 
weakness in SORF, you've alleged DORF has that weakness.

Here is an example:
 ...
(by the way, you've used SORF syntax in those examples)

 It doesn't make any sense to apply your functions to my records or vice-
versa,

Exactly! and that's what the DORF design avoids, whereas SORF suffers from it.

 but because we both chose the
 same label,

SORF uses the same label in the sense of the same String Kind.

 the compiler allows it. Putting the code in separate modules makes no 
difference, since
 labels are global.

DORF's labels are not global, they're proxy _types_ so that the scope is 
controlled in the usual way. So using separate modules makes all the 
difference.

 
 Here is a simple solution, using SORF:
 ...

I think your solution would work just as well 'translated' into DORF.

(But then it's a solution to something that isn't a problem in DORF.)

 
... than building the mechanism in to the language as DORF does, ...
 
 Barney.
 

DORF is not building the mechanism in to the language, nor is it introducing 
any new language features, only sugar. The prototype runs in GHC v7.2.1. All 
I've done is hand-desugarred. (Look at it for yourself, it's attached to the 
implementor's page.)

SORF, on the other hand, needs user-defined Kinds, which are only just being 
introduced in v7.4, and don't yet include String Kind.

AntC





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


Re: Records in Haskell

2012-02-28 Thread AntC
Gábor Lehel illissius at gmail.com writes:

 
 2012/2/25 Gábor Lehel illissius at gmail.com:
  Please correct me if I've misunderstood or mischaracterized any aspect of 
DORF.
 
 Okay, I did end up misunderstanding and mischaracterizing at least two
 aspects of DORF.
 
 Re-reading the wiki page:
 
 
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
 

Sorry, Gábor, but you've still mis-understood. I tried so hard to explain it 
clearly!

 it's clear that you would not have to write fieldLabel declarations
 for every single field of every single record,

But yes you do have to declare every fieldLabel that's going to appear in a 
record decl within a module compiled under DORF. (Even if the field only 
appears once in one record -- sorry!)

You can, though, mix records/fields from modules compiled under H98 monomorphs 
(providing no clash of names!)

 only for the ones you
 wish to be shared and usable polymorphically. By default, fields of
 individual records would be specific to that record (monomorphic in
 the type of the record),

No! the record decl would (try to) generate an instance for every field of 
every record, then the compile would fail because there was no fieldLabel 
declared.

 So the difference between DORF and my variant would be:
 ...

(You've misunderstood DORF, so got the next bit wrong.)

 
 It wasn't clear to me before that DORF retains record-monomorphic
 fields, ...
(It doesn't!)
 In DORF you can
 presumably still use a record-monomorphic field selector to help infer
 the concrete type of the record

Kind-of: you can declare a fieldLabel with a monomorphic type (if you want it 
to only appear in a single record), then it helps type inference.

 ... 
 One troubling consequence of DORF -- again, if I'm understanding
 things correctly -- is that due to implicit field instances a module
 import can change the meaning of your program:

No you aren't understanding correctly, so: no, a module import can't change 
the meaning. (It might mean the program fails to compile, due to name clash.)

I've responded to same later posts to clarify this.

AntC


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


Re: Records in Haskell

2012-02-28 Thread AntC
Henrik Nilsson nhn at Cs.Nott.AC.UK writes:

 
 Hi,
 
 Just checking my understanding here as I have not followed this thread
 in all its details.
 
 So, with both DORF ''', am I correct in understanding
 that polymorphic fields, be it universally quantified as in
 

Good question Henrik! It's explicitly answered in the wiki, because it's a 
tricky area. Briefly:
- both of those varieties of poly fields are possible
- both can be declared in records
- both can be extracted and applied in polymorphic contexts
- DORF supports updating the universally quantified,
  including changing the type of the field and therefore of the record.
  (Also there's a Quasifunctor proposal for SORF to do that.)
- Neither approach supports updating the existential/higher-ranked variety.

(There are all the complexities you discuss in detail. They are solved (with 
quite a bit of complexity behind the scenes), except for updating h-r types.)

You can still use explicit data constructurs to pattern match and update h-r 
fields.

Question for you: (you've already given an example of wanting to update a 
universally quant'd field and change its type)
   Do you want to update a h-r field?
   If so, what's the use case?

AntC

 data ARecordType a =
  C1 {
  ...,
  fieldX :: a,
  ...,
  fieldY :: a - a,
  ...
  }
 
 or existentially quantified as in:
 
 data AnotherRecordType =
  forall a . C2 {
  ...,
  fieldU :: a,
  ...,
  fieldV :: a - Int,
  ...
  }
 
 would no longer be possible?
 
 Note that the type variable a in both cases scope just over the
 constructor(s) of the data type in question. So any attempt at
 declaring the types of the fields outside of this context,
 be it explicitly with the fieldLabel notation, or implicitly as
 per your proposal, would not be possible. E.g.
 
 fieldLabel fieldY :: a - a
 
 would presumably mean
 
 fieldLabel fieldY :: forall a . a - a
 
 resulting in ARecordType becoming second-order polymorphic
 where the value of fieldY would *have* to be a polymorphic function,
 which is very different from the original definition.
 
 Similarly, the whole point with the existentially quantification is
 to allow a number of fields to share some specific but arbitrary type,
 which again means that any attempt to type these fields outside of the
 context of the datatype to which they belong would result in something
 different.
 
 Note that fieldU and fieldV cannot be used as projection functions
 due to escaped type variables, but that field selection by pattern
 matching is perfectly fine.
 
 Both constructions above are very useful and, I'd argue that a design
 that rules them out actually is a rather poor fit for a language like
 Haskell.
 
 To be completely honest, I, at least, would be much happier keeping
 working around the present limitations of Haskell's named fields by
 picking my field names carefully, than losing the above.
 
 Or am I missing something? E.g. is the idea that sharing of fields
 only applies to fields of monomorphic type, i.e. whose type can be
 declared globally?
 
 Best,
 
 /Henrik
 





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


Re: Records in Haskell

2012-02-28 Thread AntC
J. Garrett Morris jgmorris at cs.pdx.edu writes:

 
 Has x f has no semantic content besides type x having an f field; Ord
 has (at least in the programmer's mind, even if the language can't check
 it) meaning beyond the simple presence of a compare function.
 
  /g
 

Note that under both SORF and DORF, there are three arguments to the `Has` 
class. The third is specifically to spec or constrain the type of the result.

A decl:

data Rec a = Ord a = Rec{ flda :: a }

Expects:

flda :: (r{ flda :: a }, Ord a) = r - a

Where the {...} in the constraint is sugar for the Has class. (DORF and SORF 
differ slightly in how that's implemented.)

AntC


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


Re: Records in Haskell

2012-02-28 Thread AntC
Barney Hilken b.hilken at ntlworld.com writes:

 
 
  This should be used to generate
  internal constraints and not be exposed to the end user and not
  automatically abstract over fields.
 

Barney, I'm not going to try to defend or explain what Greg means by that 
comment, but I do want to talk about:

 insistence that the Has class should be hidden from the user.
 ...
 I think the Has class would be useful to programmers and
 no harder to understand than other Haskel classes. It should not be hidden.
 
 Barney.
 

I agree that what the `Has` class is doing is useful, and indeed the 
programmer needs to understand it.

SPJ suggested syntactic sugar for the Has class. The DORF proposal embraces it 
whole-heartedly, and expects the programmer would use the sugar. There's two 
reasons for avoiding writing explicit `Has`:

1. It's tricky syntax and easy to get wrong.
   Specifically, all your examples in later posts have confused it.
2. The implementation of overloadable record fields (whether SORF or DORF)
   is going to be tricky to get right. We'll need equality and class
   constraints. There needs to be some space for the implementors to tune
   the design.

I think the sugar is hiding the implementation, not the existence of the `Has` 
class -- as is good practice.

AntC





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


Re: Records in Haskell

2012-02-28 Thread AntC
Greg Weber greg at gregweber.info writes:

 
 I looked at the DORF implementers view
 
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
/ImplementorsView
 
 It appears that we still have no solution for record updates that
 change the type of a polymorphic field.

There's two varieties of polymorphic fields:
- the type-changing variety
  DORF has a solution for update/changing the type of field and record
 (always has since the proof of concept in December)
  SORF has a speculative suggestion of Quasifunctor
(looks like this needs tightening up??)
- the higher-ranked variety
  neither proposal has a way of updating
 (well, DORF did but it's an unscalable hack [SPJ],
  I put it on the wiki anyway, in case somebody can improve it)


AntC


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


Re: Records in Haskell

2012-02-28 Thread AntC
Oliver Batchelor saulzar at gmail.com writes:

 
 Hi,
 
 
  Wrong: You cannot use a fieldLabel `name` declared in module/namespace A to
  access a record with a field `name` declared in module B. You'll get a 'no
  instance' compile fail. Same familiar rules as for any instance resolution.
 
  This is the crucial difference compared to SORF: which can't control the 
scope
  of its String Kind. (Apologies that I added a speculative discussion of
  whether DORF could use String Kinds. I said that if doing so would open
  the 'back door' to the abstraction, then I'll stick with types.)
 
 
 Perhaps this situation could occur though?
 
 Module A
 fieldLabel name String
 
 Module B
 import A -- unknowingly picking up the name label
 
 data Foo = Foo { name :: String } -- uses the name label by accident
 
 So there'd have to be some syntax to make sure you intend to use a
 label rather than accidentally use it?
 (Not that this is a big issue, the situation is surely minor compared
 to sharing unrelated labels all the time)
 
 Oliver
 

Thanks Oliver, hmm ...

Did module B import A unqualified?

Did module B not have its own declaration of fieldLabel `name`?
And presumably module B has set the option to use DORF.

Then DORF is going to take it that you mean to share the `name`. (And actually 
I don't see much harm resulting.)

Them's the rules.

If there's a fieldLabel `name` in Module B, Foo will use that.
If furthermore B imports A unqualified, that's a clash of fieldLabels, so 
compile fail.
If module B is compiled with H98 style records, there's a name clash with the 
H98 field selector function.

I think this is no worse (and no better) than business-as-usual 'accidental' 
usage-without-declaration matching an unknowingly imported binding.

(As part of the 'minimal changes' requirement, I'm trying to avoid syntax 
changes to record decls.)

AntC




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


Re: Records in Haskell

2012-02-28 Thread AntC
Oliver Batchelor saulzar at gmail.com writes:

 
 I think the DORF approach is quite principled in it's namespacing. The
 labels are just normal functions which can be exported and imported
 between modules. I believe that is it's main strength - so I think to
 say it only solves the narrow name-spacing issue within a module. is
 not quite accurate.
 

Thank you Oliver, yes you got it. And very restrained of you to say not quite 
accurate. In the following I shall try to do the 'egoless programmer' thing.

Seeing as DORF's control over namespacing is a considerable improvement over 
SORF (in my view), I'm particularly miffed to see an allegation that it can't 
do EXACTLY WHAT IT'S DESIGNED TO DO.

And since that allegation has been repeated in several places, just so 
there's no probable possible shadow of doubt, no possible doubt whatever, 
I've updated the wiki with an illustration:
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
#ImportExportandRepresentationhiding
and attached a working example to the implementor's page.

The example shows that within a single record decl:
  0. You can import fieldLabel decls.
  1. You can create fields that share Labels with imports.
  2. You can create fields that don't share, even with the same Label name.
   (That is, the module system continues to control the namespace.)
  3. You can prevent using the wrong field selector with the wrong record type,
even if they have the same Label name.

Points 2 and 3 are there especially for all the people who want multiple 
`name`s that label String fields but don't mean the same thing.

The example shows that if you use the wrong `name` selector with the wrong 
record type, you get an instance failure (even if the record type has a field 
`name`).

Just before they slip on the straightjacket for all this mumbling about what's 
in a name, one further point:

- if there's a difference of meaning going on,
- you can use the type system to manage your meanings,
- with a newtype to screen the representation.

That's what Chris Done's example is doing, and it's a good discipline to 
manage complex data structures. (Thank you Greg for posting it back on to the 
Records wiki front page). 
http://hackage.haskell.org/trac/ghc/wiki/Records#Problemswithusingthecurrentmod
ulenamespacemechanism

Chris's post is what started me down the track of designing DORF, as an 
improvement over SORF, and to avoid the suggestions of sub-modules.

AntC





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


Re: Records in Haskell

2012-02-27 Thread AntC
Greg Weber greg at gregweber.info writes:
 
 
  What on earth do you mean by not automatically abstract
  over fields?
 
 Abstraction over fields is the ability to write a function that works
 on two records with the same field label.
 

Thanks Greg, I see you've put something on the wiki about abstract over 
fields. The example code doesn't seem to be right, so I'm still confused what 
you mean ...

The example has:
getA = r.a

I think that should be:
getA r = r.a

(Otherwise how does `getA` know which record to extract the `a` from?)

And you give no type signature for getA so (at a wild guess) by abstract you 
mean that `getA` extracts the `a` from any record `r` with an `a` field(?)

Under SORF: r.a desugars to a call to the `get` method.

Under DORF: r.a desugars to (a r), then we can eta-reduce:
getA r = r.a == (a r)
getA = a

Either way, I don't see that `getA` is adding anything over plain field `a`.

There _is_ a difference between DORF and SORF here. In DORF I can declare:

getF f r = r.f -- works for any field of any record
   -- RHS desugars to (f r), so getF === ($)

And can use it, for example:
getF lastName cust1
getF fullName person2

I don't think you can do this is SORF (but please check with SPJ). In 
particular, I don't think you could call this function and pass an argument 
into it for the field name.

That's because in SORF the dot notation is desugarred at the point it occurs 
(according to the wiki on SORF), and the `f` appearing on the RHS is a bound 
variable, not a field name as such. (In fact, I wonder if SORF would take the 
dot notation and try to desugar it to field f, then either get a type 
failure or (by accident) extract the wrong field.)

Please correct this on the wiki.

AntC



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


Re: Records in Haskell -- updating higher-ranked fields: required?

2012-02-27 Thread AntC
Greg Weber greg at gregweber.info writes:

 
 
  No, I don't think anybody has a satisfactory approach to
  updating polymorphic/higher-ranked fields. (DORF mentions
  one, but it's a ghastly hack.
 
 So are the proposals dead until this is tackled, or should SORF/DORF
 propose not to allow that?
 

That's an important question. I've asked in the DORF proposal how big is the 
demand to update h-r fields?

Note that is something you can do currently with H98 records/fields.

Is it good enough to be able to extract and use h-r fields in polymorphic 
contexts? (Both SORF and DORF can do that.)

Is it good enough to be able to create records with h-r fields (using the data 
constructor)?  (Both SORF and DORF can do that.)


AntC


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


Re: Records in Haskell

2012-02-23 Thread AntC
Greg Weber greg at gregweber.info writes:

 
 Thanks to Anthony for his DORF proposal, and spending time to clearly
 explain it on the wiki.
 
 I have a big issue with the approach as presented - it assumes that
 record fields with the same name should automatically be shared. As I
 have stated before, to avoid circular dependencies, one is forced to
 declare types in a single module in Haskell that would ideally be
 declared in a multiple modules. ...

Thanks Greg, but I'm struggling to understand what the difficulty is with 
sharing the same name, or why your dependencies are circular. Would you be 
able to post some code snippets that illustrate what's going on (or what's 
failing to go on)?

Or perhaps this is an experience from some application where you weren't using 
Haskell? Could you at least describe what was in each record type?

 Continuing the database example, I
 will have multiple tables with a 'name' column, but they do not have
 the same meaning.
 
 If I have a function:
 
   helloName person = Hello,  ++ person.name
 
 The compiler could infer that I want to say hello to inanimate objects!

So the first question is:
* do your fields labelled `name` all have the same type? (Perhaps all String?)
* what meaning does a name have beyond being a String?

Your code snippet doesn't give the types, but if I guess that you intend 
`person` to be of type `Person`. Then you can give a signature:
 helloName :: Person - String

If person can be 'anything' then the type inferred from the bare function 
equation would be:
 helloName :: r{ name :: String } = r - String

So you could say hello to your cat, and your pet rock. You couldn't say hello 
to a pile of bricks (unless it's been given a name as an art installation in 
the Tate Gallery ;-)



 Note that I am not completely against abstraction over fields, I just
 don't think it is the best default behavior.
 

So what is the best default behaviour, and what is the range of other 
behaviours you want to support?


 And the section Modules and qualified names for records shows that
 the proposal doesn't fully solve the name-spacing issue.
 

I think it shows only that record field labels can run into accidental name 
clash in exactly the same way as everything else in Haskell (or indeed in any 
programming language). And that Haskell has a perfectly good way for dealing 
with that; and that DORF fits in with it.

Greg, please give some specific examples! I'm trying to understand, but I'm 
only guessing from the fragments of info you're giving.

AntC




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


Re: simple extension to ghc's record disambiguation rules

2012-02-19 Thread AntC
Hi, I'd like to propose an extremely simple extension to ghc's record 
disambiguation rules, 

I wonder if John is teasing us? Nothing wrt to records is simple (IMHO).

John seems to be unaware of the threads on 'Records in Haskell' (ghc-users)
or 'Type-Directed Name Resolution' (cafe) that have been storming for the
last few months.

He refers to a web page ...
 ideally it would be combined with the 'update' and 'label-based 
 pattern-matching' extensions from this page 
 http://hackage.haskell.org/trac/haskell-prime/wiki/ExistingRecords

... which is several years old, requesting features that have been largely
delivered in
ghc's -XDIsambiguateRecordFields, -XNamedFieldPuns, and -XRecordWildCards.


 my motivation is that I often have record types with multiple constructors 
 but common fields. 

Perhaps this is a different requirement to those threads above?
Most are dealing with the namespacing problem of common fields in different
record types.
I think John means common fields under different constructors within the
same type(?).


 so, my proposal is that when you come across something like 

 (e::RecType) { blah = foo } 

 (with an explicit type signature like shown) 

It's certainly an innovation to go looking for an explicit type sig. within
an expression.
Does anything else in Haskell do that?


 It ... would be a new thing 
 for patterns which generally don't allow type signatures there. 

 It sidesteps type checker interactions by only being triggered when an 
 explicit type annotation is included. 

John 

Extremely simple? I don't think so.

I've added a suggested approach to approximate what John is asking for to my
DORF proposal.
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields/PolyRecordPattern
-- as a **speculative** **future** development.

The ease with which I could do that (both a polymorphic record update _and_
polymorphic record pattern match) suggests my proposal is powerful enough to
achieve the limited aims for the namespacing issue, with some headroom. --
But then I would say that, wouldn't I!

(By the way, none of the 'Records in Haskell' proposals describe themselves
as extremely simple.
http://hackage.haskell.org/trac/ghc/wiki/Records

AntC


--
View this message in context: 
http://haskell.1045720.n5.nabble.com/simple-extension-to-ghc-s-record-disambiguation-rules-tp5494549p5497846.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://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell - namespacing for fields

2012-01-31 Thread AntC
John Lask jvlask at hotmail.com writes:

 
 On 1/02/2012 12:26 AM, AntC wrote:
 
  No! no! no! For records _don't_ put records in nested/sub-modules, and 
_don't_
  require them in separate modules (as currently). Here's how ...
 
 
 namespace management and record systems are intimately related, but as 
 you assert distinct issues.
 
 taking your example of Customer_id, I expressly want to be able to 
 define in the same syntactic module (file). Two records with a field 
 with exactly the same name at two different types, say Customer_id :: 
 Int and Customer_id :: String. As I understand it, your proposal
 would not enable this.

John, you can't do this now. You can't even define in the same module two 
records with the same name with the _same_ type.

[I'd better check first why you've put Customer_id with upper case, that's a 
type, not a field. Are you sure what you're talking about?]

I'd certainly dispute that there's anything sensible in doing that (why? 
what's the use case?), and I guess my proposal is not making that easy, but it 
is possible (and in fact no more difficult than a 'fixed' type for a field).

You'd go:
  field customer_id :: r - t  -- which is the same as no type spec at all
Then:
  data CustInt = CustInt { customer_id :: Int, ... }
  data CustString = CustString { customer_id :: String, ... }
It doesn't stop you also doing:
  data CustBool = CustBool { customer_id :: Bool, ... }

(I could contrive that the domain of customer_id is constrained to only Int or 
String, but why?)

 
 In reality these two different uses of the name Customer_id are 
 unrelated and distinct. Some would argue that therefore they should 
 rightly have distinct names, however that is moot, for the purpose of 
 this discussion lets take this as the objective.

No, I'm not going to take that as an objective. You'd have to provide a much 
better motivation for wanting to have two identical names in the same scope 
that are unrelated and distinct.

I'd agree with the 'some' that you should use two different names. Or if this 
is an 'accidental' clash of names from developers working separately (this is 
my distant planet example), then the clash is not special for field names, and 
it's what the module system is for. Use My.customer_id and Their.customer_id.

 
 There are two roads to travel: Customer_id is one semantic entity (in 
 the sense of an overloaded field, disambiguated by the type system) or 
 Customer_id represents two distinct semantic entities disambiguated 
 syntactically. I for one favor the second approach as it matches my 
 intent, can I say, more faithfully.
 

I'm interested to know how you disambiguate syntactically distinct entities 
with identical names in the same scope.

  [There may be other reasons for nested/sub-modules, but records ain't it.]
 
 as above, however, I believe the best approach is to explore both paths 
 and perhaps extend Haskell in both directions.
 

No, we can't afford to keep exploring multiple paths. What happens in fact is 
that it's extremely hard work, there's very few people who can actually 
implement it, they (frankly) are not very interested when there's so many 
other exciting possible developments. (Record systems don't count as exciting 
for programming language research: the ground is already well covered.) 
There's barely the resourcing to extend Haskell in just one way, and only 
providing the change is minimal.
Haskell 98's record system has been a wart since -- errm -- 1996.


 As in your example the particular construction of which suits, the 
 approach offered in your email better because it matches your intent 
 more faithfully. It is this ability to match construction with intent 
 that is critical, which alludes to the notion of the expressivity of a 
 language.
 

Eh? This sounds like metaphysics.


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


Re: Holes in GHC

2012-01-26 Thread AntC
Thijs Alkemade thijsalkemade at gmail.com writes:

 
 On Thu, Jan 26, 2012 at 8:33 PM, Simon Peyton-Jones
 simonpj at microsoft.com wrote:
 
  I'm sorry to be slow, but I still don't understand what you intend. 

Hi Thijs, like Simon, I'm struggling to see the point. You said earlier:

 The intended users are people new to Haskell or people working with existing 
 code they are not familiar with.

I would expect newbies to at least work through some tutorials or 'try Haskeel 
on-line' before being let loose at the GHCi prompt.

 
 The primary goal is to make this part of GHCi. Say, you're working on
 a file Foo.hs in your favorite editor, and you have:
 
 ---
 
 foo = foldr __ 0 [1..5]
 
 ---
 
 And you have no idea what you should use at the location of the __.
 You bring up GHCi, and load it as a module:
 

I would do:
:t foldr
or
:t \__f - foldr __f 0 [1..5]

If the user doesn't know why asking for the type of a term would help, or 
can't figure out which sub-term they need to worry about, or doesn't 
understand the type they get back, I don't see that any fancy extension to 
GHCi is going to help much.

AntC



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


Re: Records in Haskell

2012-01-26 Thread AntC
Ryan Newton rrnewton at gmail.com writes:

 
 I admit I'm a big fan of polymorphic extension.  But I don't love it enough 
for it to impede progress!  
 
 Regarding extension:  In trying to read through all this material I don't 
see a lot of love for lacks constraints a la TRex.  
 Cheers,
   -Ryan
 
Hi Ryan, I think the lacks constraint is sadly misunderstood, and in fact 
something like it will be needed eventually.

(If anybody who knows the internals of Hugs/TRex is listening, it would be 
great to get confirmation of the following.)

As you say, it relates to whatever might happen for polymorphic records, so is 
outside the scope of what SPJ is trying to address in this thread.

On the other hand, let's try to avoid developing an approach for 'Records in 
Haskell' that has to be undone when/if we get more polymorphic.

[Weird! somewhere between gmaniac and pipermail, half my post went missing: I 
was only just warming up this far. Try again ...]

From all the suggestions in the current thread, I'm expecting the approach 
will include a Has class with methods get and set. It would be sweet if in 
future the same Has class could be extended to extended(!) records, anonymous 
records, renamed labels, projections on records, merged records (as you'd get 
from a relational join), etc. Specifically:
  Has r l t = ... really must mean 
 there's exactly one field labelled l in record r, at type t
 (which is a constraint on whatever merged/extended term r is)
compare TRex's
  (r\l) = ... Rec {| l : t | r |} ...   which really means
 there's exactly one field labelled l in the Rec, at type t

In hindsight, I think it was unfortunate that the original TRex paper [1] used 
the word lacks in context of its notation for constraining the record 
structure. (I'm looking especially at section 2.1 'Basic Operations'.) In all 
the operations, the types always include a Rec term with _both_ l and r. They 
don't all have a term of a 'bare':
  Rec {| r |}
TRex is trying to avoid a positional specification of the record fields (which 
is 'implementation determined'/hidden from the programmer). But I think 
of 'bare' r as representing a record with a 'hole' at whatever position l is 
in the full record. (So the constraint (r\l) means: you're going to find a Rec 
with exactly one l in it; if you also find a Rec with 'bare' r, that means the 
same Rec, but with a 'hole'.)

The HList guys picked up the word lacks, and adapted it (successfully in 
context of what they were doing) to build 'Type Indexed Hlist's -- that is, 
record-like structures with exactly one field labelled l.

Perhaps TRex should have used a notation something like:
   (rr : l @ t) = Rec {| rr |} ...   -- HasUnique rr l t
   ... Rec {| rr \ l |} ...-- rr with a hole in place of l


You say:
  As one anecdote, I've been very pleased using Daan Leijen's scoped labels 
approach
My anecdote: the new approaches and extensions to type inference in GHCi have 
been frustratingly slow in arriving and maturing. But we now have working 
superclass constraints, including type equality (~), and some heavy-weight 
type inference. I've built a toy (and somewhat limited) polymorphic record 
system (with Has/get/set), which:
treats Data types as records; and
treats tuples as anonymous (type-indexed) records; and
implements project, extend and merge.
It relies on overlapping instances (so I don't mention it in polite company -- 
at least it doesn't use FunDeps to boot!). I achieve the effect of 'HasUnique' 
through instance resolution: if there's more than one occurence of label l in 
the record term, GHC bitches. (This is fragile: I can't use 
IncoherentInstances, and sometimes UndecidableInstances gives trouble.)


[1] A Polymorphic Type System for Extensible Records and Variants, Gaster/Mark 
P. Jones, 1996.



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


Re: Records in Haskell

2012-01-26 Thread AntC
Ryan Newton rrnewton at gmail.com writes:

 I admit I'm a big fan of polymorphic extension.  But I don't love it enough 
for it to impede progress!  
 
 Regarding extension:  In trying to read through all this material I don't 
see a lot of love for lacks constraints a la TRex.  
 Cheers,
   -Ryan
 
Hi Ryan, I think the lacks constraint is sadly misunderstood, and in fact 
something like it will be needed eventually.

[Weird! somewhere between gmaniac and pipermail, half my post went missing: I 
was only just warming up this far. Try again ... again ...]

(If anybody who knows the internals of Hugs/TRex is listening, it would be 
great to get confirmation of the following.)

As you say, it relates to whatever might happen for polymorphic records, so is 
outside the scope of what SPJ is trying to address in this thread.

On the other hand, let's try to avoid developing an approach for 'Records in 
Haskell' that has to be undone when/if we get more polymorphic.

From all the suggestions in the current thread, I'm expecting the approach 
will include a Has class with methods get and set. It would be sweet if in 
future the same Has class could be extended to extended(!) records, anonymous 
records, renamed labels, projections on records, merged records (as you'd get 
from a relational join), etc. Specifically:
  Has r l t = ... really must mean 
 there's exactly one field labelled l in record r, at type t
 (which is a constraint on whatever merged/extended term r is)
compare TRex's
  (r\l) = ... Rec {| l : t | r |} ...   which really means
 there's exactly one field labelled l in the Rec, at type t

In hindsight, I think it was unfortunate that the original TRex paper [1] used 
the word lacks in context of its notation for constraining the record 
structure. (I'm looking especially at section 2.1 'Basic Operations'.) In all 
the operations, the types always include a Rec term with _both_ l and r. They 
don't all have a term of a 'bare':
  Rec {| r |}
TRex is trying to avoid a positional specification of the record fields (which 
is 'implementation determined'/hidden from the programmer). But I think 
of 'bare' r as representing a record with a 'hole' at whatever position l is 
in the full record. (So the constraint (r\l) means: you're going to find a Rec 
with exactly one l in it; if you also find a Rec with 'bare' r, that means the 
same Rec, but with a 'hole'.)

The HList guys picked up the word lacks, and adapted it (successfully in 
context of what they were doing) to build 'Type Indexed Hlist's -- that is, 
record-like structures with exactly one field labelled l.

Perhaps TRex should have used a notation something like:
   (rr : l @ t) = Rec {| rr |} ...   -- HasUnique rr l t
   ... Rec {| rr \ l |} ...-- rr with a hole in place of l


You say:
  As one anecdote, I've been very pleased using Daan Leijen's scoped labels 
approach
My anecdote: the new approaches and extensions to type inference in GHCi have 
been frustratingly slow in arriving and maturing. But we now have working 
superclass constraints, including type equality (~), and some heavy-weight 
type inference. I've built a toy (and somewhat limited) polymorphic record 
system (with Has/get/set), which:
treats Data types as records; and
treats tuples as anonymous (type-indexed) records; and
implements project, extend and merge.
It relies on overlapping instances (so I don't mention it in polite company -- 
at least it doesn't use FunDeps to boot!). I achieve the effect of 'HasUnique' 
through instance resolution: if there's more than one occurence of label l in 
the record term, GHC bitches. (This is fragile: I can't use 
IncoherentInstances, and sometimes UndecidableInstances gives trouble.)


[1] A Polymorphic Type System for Extensible Records and Variants, Gaster/Mark 
P. Jones, 1996.



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


Re: Records in Haskell

2012-01-26 Thread AntC
Ryan Newton rrnewton at gmail.com writes:

 
 I admit I'm a big fan of polymorphic extension.  But I don't love it enough 
for it to impede progress!  
 
 Regarding extension:  In trying to read through all this material I don't 
see a lot of love for lacks constraints a la TRex.
 Cheers,
   -Ryan

Hi Ryan, I think the lacks constraint is sadly misunderstood, and in fact 
something like it will be needed eventually.

[A further thousand apologies for the multi-multiposts! somewhere in pipermail
 half my posts are going missing: I was only just warming up this far. Try 
again ... again ... third time ... last time]

(If anybody who knows the internals of Hugs/TRex is listening, it would be 
great to get confirmation of the following.)

As you say, it relates to whatever might happen for polymorphic records, so is 
outside the scope of what SPJ is trying to address in this thread.

On the other hand, let's try to avoid developing an approach for 'Records in 
Haskell' that has to be undone when/if we get more polymorphic.

All the suggestions in the current thread lead to an approach with a Has class 
with methods get and set. It would be sweet if in future the same Has class 
could be extended to extended(!) records, anonymous records, renamed labels, 
projections on records, merged records (as you'd get from a relational join), 
etc. Specifically:
  Has r l t = ... really must mean 
 there's exactly one field labelled l in record r, at type t
 (which is a constraint on whatever merged/extended term r is)
compare TRex's
  (r\l) = ... Rec {| l : t | r |} ...   which really means
 there's exactly one field labelled l in the Rec, at type t

In hindsight, I think it was unfortunate that the original TRex paper [1] used 
the word lacks in context of its notation for constraining the record 
structure. (I'm looking especially at section 2.1 'Basic Operations'.) In all 
the operations, the types always include a Rec term with _both_ l and r. They 
don't all have a term of a 'bare':
  Rec {| r |}
TRex is trying to avoid a positional specification of the record fields (which 
is 'implementation determined'/hidden from the programmer). But I think 
of 'bare' r as representing a record with a 'hole' at whatever position l is 
in the full record. (So the constraint (r\l) means: you're going to find a Rec 
with exactly one l in it; if you also find a Rec with 'bare' r, that means the 
same Rec, but with a 'hole'.)

The HList guys picked up the word lacks, and adapted it (successfully in 
context of what they were doing) to build 'Type Indexed Hlist's -- that is, 
record-like structures with exactly one field labelled l.

Perhaps TRex should have used a notation something like:
   (rr : l @ t) = Rec {| rr |} ...   -- HasUnique rr l t
   ... Rec {| rr \ l |} ...-- rr with a hole in place of l


You say:
  As one anecdote, I've been very pleased using Daan Leijen's scoped labels 
approach.
My anecdote: the new approaches and extensions to type inference in GHCi have 
been frustratingly slow in arriving and maturing. But we now have working 
superclass constraints, including type equality (~), and some heavy-weight 
type inference. I've built a toy (and somewhat limited) polymorphic record 
system (with Has/get/set), which:
treats Data types as records; and
treats tuples as anonymous (type-indexed) records; and
implements project, extend and merge.
It relies on overlapping instances (so I don't mention it in polite company -- 
at least it doesn't use FunDeps to boot!). I achieve the effect of 'HasUnique' 
through instance resolution: if there's more than one occurence of label l in 
the record term, GHC bitches. (This is fragile: I can't use 
IncoherentInstances, and sometimes UndecidableInstances gives trouble.)


[1] A Polymorphic Type System for Extensible Records and Variants, Gaster/Mark 
P. Jones, 1996.
 





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


Record update for Higher-ranked or changing type via Has/get/set [was: Records in Haskell]

2011-12-13 Thread AntC

Firstly, thank you to SPJ for putting some detailed design into 'Overloaded 
record fields' [SPJ 1].
What I'm showing here draws heavily on the techniques he demonstrates.

I wasn't happy with several parts of the design proposal;
especially not with the amount of not-yet-available type machinery it involved 
(explicit type application, anonymous types, the kind system, String types).

But then SPJ wasn't happy himself with the limitations on Record update for 
polymorphic fields:
This problem seems to be a killer: if record-update syntax is
 interpreted as a call to `set', 

It's (too) easy to chuck rocks - the glaring weakness of (Haskell's record 
system) is still a swamp despite a pile of rocks (to mix my metaphors).


This posting (as a .lhs) is the result of exploring within the narrow issue: 
namespacing for record field names.
I've used GHC + recent type extensions (v7.2.1). Findings in short:
- I've followed SPJ with a `Has' class, and methods `get' and `set'.
- I seem to have a way to update Higher-ranked fields,
- and change the type of the record,
- and even update Existentially-quantified fields (to a limited extent)
 - which should please the object-oriented oriented.

I'd appreciate some feedback:
- Have I misunderstood the results?
- Are there still unacceptable limitations?
 (Certainly the error messages are impenetrable when you go wrong.)
- The `Has' class, instances and type functions are ugly
 - can we be more elegant?
(I expect the instances to be generated systematically from the data
 decl. So usually the application programmer won't have to see them.
I like SPJ's 'Syntactic sugar for Has' to pretty-up Has constraints.)

Disclaimer:
- I'm keeping close to SPJ's objective of improving the situation w.r.t.
name clashes for record fields. [SPJ 2]
- I'm _not_ claiming this is a design for 'first class record types'
/extensible records/record polymorphism.
- I'm _not_ making a proposal for 'Records in Haskell'.
(Not yet: if this is approach is deemed 'workable',
 then I have a design in mind.)
- I'm _not_ envisaging anything like 'first-class labels'.
(I think that idea is probably not the right objective,
 but that's a debate for another day.)

The basic idea:
- Field selection uses dot notation as reverse-application,
  applying a field selector via Has/get and resolving the instance to the
  record type and field, that is:
r.fld == fld r, == get (undefined :: Proxy_fld) (r@DCons{fld}) = fld
   (I've used (.$) = flip ($) to fake the syntax for dot notation.)
- Record construction and pattern matching with explicit data constructors
  works as with -XDisambiguateRecordFields
- Record update uses H98 syntax, to be compiled to Has/set
  and resolving the instance to the record type and field with explicit data
  constructor:
r {fld = val} == set fld val (r@DCons{..}) == DCons{fld = val, ..}
-- using Puns and WildCards
(I've used (.=) = set to fake the syntax for update: r.$(fld.=val).)
- Of course, I can't use the field name itself, because that would clash with
  the H98 selector. Instead:
_fld = undefined :: Proxy_fld   -- for the update syntax
fld_ = get (undefined :: Proxy_fld) -- for the (overloadable)
-- selector function

The approach uses a 'loose coupling' between the type arguments of Has/get/set,
with type functions to control the linkage.
  (Some could be Associated Types -- a matter of taste?)

The recipe needs:

 {-# OPTIONS_GHC -XDisambiguateRecordFields -XNamedFieldPuns -XRecordWildCards
#-}
 {-# OPTIONS_GHC -XTypeFamilies#-}
 {-# OPTIONS_GHC -XRankNTypes  -XImpredicativeTypes -XGADTs -XEmptyDataDecls
#-}
 {-# OPTIONS_GHC -XMultiParamTypeClasses -XFlexibleInstances
  -XUndecidableInstances#-}

 module HasGetSet  where

SPJ's example of a higher-ranked data type
 -- imported so that we have clashing declarations of `rev'

  import HRrev
  {- data HR   = HR {rev :: forall a.[a] - [a]}   -}

  data Tab a b where   -- a different data type with a HR field `rev'
Ta :: {tag :: String, rev :: forall a_.([a_] - [a_]), flda :: a }
  - Tab a b
Tb :: (Num n, Show b) = {tag :: String, fldn :: n, fldnb :: n - b}
   - Tab a b
  -- Existential fields (GADT syntax)

overloadable definitions for field `rev':

  data Proxy_rev  -- phantom, same role as SPJ's String kind rev
  _rev = undefined :: Proxy_rev
  rev_ r = get (undefined :: Proxy_rev) r

build some syntax to fake the dot notation, and assignment within record