Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution -record update

2012-02-12 Thread Evan Laforge
 OK, we could implement lenses, make `tempo' a lens instead of a selector,
 desugar the update syntax to call the update 'method' out of the lens, ...
 And of course somehow arrange the sugar that when `tempo' appears in other
 contexts we take the select 'method'.

implement lenses - Done, of course.

make 'tempo' a lens instead of a selector - Done, but with TH.

desugar the update syntax - Not necessary, and normal function syntax
is more flexible than special update syntax.

arrange for 'tempo' in other contexts to be the select method - If I'm
understanding correctly, then this is also not necessary.  If we are
using normal function syntax then there are no other contexts.

 You write up the proposal, and think through all the changes it would involve
 over Haskell/GHC as is, and then we can compare it to all those other
 proposals.

So no proposal is necessary, because it's already implemented.  However:

 Now in return for me answering that, please answer the questions in my earlier
 post about what limitations on update you'd like:
 * record-type changing?
 * Higher-ranked fields?
 * How many forall'd variables?
 * Constrained forall'd variables?

If record update is a normal function then all of these questions are
moot.  However, if it uses lenses then, focusing on type changing
first, you raise a good point.  All the lens libraries I know of have
a 'set' function like 'Lens a b - b - a - a', and so can't change
the type of the record the way record update syntax can.  That's a
serious weakness, and you're right that a real proposal shouldn't go
forward without a solution for it.

I don't understand enough about the issue yet to know from where
exactly this weakness arises, and what would be needed to solve it in
the context of lenses, e.g. in a data structure that can be passed to
a normal function rather than as special syntax.  If I understood it
better then perhaps I could suggest something to address exactly that
weakness in an orthogonal way.  I'll have to think about it more.

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


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution -record update

2012-02-10 Thread Steve Horne

On 10/02/2012 03:22, Donn Cave wrote:

   modifyRecord :: RecordType r =  (a -  a) -  (r -  a) -  r -  r



   data Config { tempo :: Int, ...}
   f = modifyRecord tempo (+20)


I'm hoping I missed something, and that you don't intend the (r - a) 
part of this in particular to be taken literally.


If you intend something to be used as a field identifier, you should 
give it a type that says that. A function (r - a) could be anything - 
even a use of const that ignores the value for r. Having a type class 
for field ids, parameterized by the record type and the field type, 
would make more sense. Having that, you could treat a record a bit like 
an IORef - use polymorphic read, write and modify functions. Like an 
IORef doesn't mean mutability, of course.


Personally, though, I still quite like the existing update notation, at 
least for updating multiple fields at once. Some tweaks could be nice - 
particularly for taking an (a - a) function rather than an (a) value 
for each field.


What I might do (note - spelling choices not sanity checked).

data MyRecordT = MyRec {= field01 :: Int, field02 :: Int =}
  --  New notation to avoid breaking changes where old notation is used.
  --  This notation should not provide module-level field access functions.

example_read_1 :: FieldID MyRecordT Int - MyRecordT - Int
example_read_1 fid r = readRec fid r

example_read_2 :: MyRecordT - Int
example_read_2 = readRec MyRecordT.field01
  --  This differs from my earlier typename.fieldname gives field
  --  access function idea. More clutter here, but for a reason.

example_read_3 :: MyRecordT - Int
example_read_3 r = readRec MyRec.field01 r
  --  This would only match field01 in the MyRec constructor case, even
  --  if there were other constructors for the same type. The same type as
  --  MyRecordT.field01, but a different value.

example_read_4 :: MyRecordT - Int
example_read_4 r = r.field01
  --  Direct read of a field in a known record value is a common case,
  --  and avoiding the explicit readRec avoids clutter.


example_modify_1 :: FieldID MyRecordT Int - (Int - Int) - MyRecordT 
- MyRecordT

example_modify_1 fid fun r = modifyRec fid fun r
  --  For longhand, support modifyRec and writeRec functions

example_modify_2 :: MyRecordT- (Int - Int)- MyRecordT
example_modify_2 r fun = r { field01 fun, field02 (+field01) }
  --  First item of each pair indicates field. Lack of = indicates use 
a function.
  --  Within the braces, all the functions (second item each pair) see 
an environment
  --  containing all field names, referring to the original value of 
the record.
  --  Pair doesn't mean tuple here - just two subexpressions separated 
by whitespace.

  --  Maybe - or - separator would be better instead.

example_modify_3 :: MyRecordT - FieldID MyRecordT Int - MyRecordT
example_modify_3 r fid = r { fid (+1) }
  --  First item of each pair still accepts arbitrary field IDs. Also, 
could
  --  use MyRec.field01 - to only allow matching that field in that 
constructor.
  --  Probably require parens for anything other than a single 
identifier in the

  --  field-id subexpression.

example_modify_4 :: MyRecordT - MyRecordT
example_modify_4 r = r { field01 (\_ - readRec r.field02 r) }
  --  The dot still supplies field IDs, overriding the 
names-for-initial-values
  --  environment, for record types, data constructors, and record 
values. Using
  --  the shorthand for any reads of original field values is not 
compulsory.


example_modify_5 :: MyRecordT - MyRecordT
example_modify_5 r = r { field01 = field02, field02 (+1) }
  --  The = is still available too - mixing of write and modify cases 
supported


example_modify_6 :: MyRecordT - MyRecordT
example_modify_6 = MyRecordT { field01 = field02, field02 = field01 }
  --  Allow update shorthand for the type and for the data constructor too,
  --  giving a function as normal.

On scope, the braces imply certain environment-defining rules. Also, the 
dot introduces a very short lived environment providing the field names. 
If the record type and/or data constructor is in scope, and the field 
names are made public by the module that defines them, these notations 
should just work - can't (and no need to) explicitly import the field 
names, which would import them into the wrong scope anyway. Importing 
the type name brings the field names along with it for type- and 
value-related scopes (such as typename.fieldname and 
value.fieldname) and importing the data constructor name brings the 
field names along with it for constructor-related scopes (such as 
datacons.fieldname).


Ban having type name, data constructor name or field name the same for 
the same type, except that a field name can occur within several data 
constructors for the same type - but only when using this record syntax. 
This is in part to avoid confusion within the braces notation for 
update. There is no ambiguity in principle, though, because the new 
environments hide any conflicting identifiers 

Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution - record update

2012-02-09 Thread AntC
Donn Cave donn at avvanta.com writes:

 
 Quoth Evan Laforge qdunkan at gmail.com,
 ...
  The non-composing non-abstract updates are what bug me, and
  make me scatter about tons of 'modifyThis' functions, both for
  composability and to protect from field renames.
 
 So ... at the risk of stating the obvious, is it fair to say the root
 of this problem is at least the lack of `first class' update syntax?

No, Donn, it's not the lack of syntax, it's the lack of semantics for first-
class (polymorphic) record update. And there's very little that's obvious. SPJ 
was not very happy with any of this.

SPJ in the SORF proposal asks:
what does e { x = True } mean if there are lots of x fields in scope?
(which is precisely what we want to allow)

So he's supposing some syntax -- where `e' is some expression that evaluates 
to a record. (There's a shorter discussion in the TDNR proposal.)

If Haskell supported polymorphic update semantics (as well as polymorphic 
field selection), you could build for yourself all those update idioms you 
talk about.

More abstractly, can Haskell offer a polymorphic `set' (and `get') method for 
the `Has' class?

set :: (Has r fld t) = fld - t - _r - r
get :: (Has r fld t) = r - fld - t -- fld in record r at type t
-- where fld is a type/Kind that identifies the field

The SORF proposal discusses lots of awkward cases which make polymorphic 
update difficult.

I've built a prototype that hacks round some of those cases. SPJ's view (on a 
quick inspect) is that it's workable in some cases, limited in others, and not 
scalable in general.

Are you/everybody here prepared to give away some of the current record 
features so that you can go poly?

- Do you want to change the type of a record?
  (that's why I've put `_r' in `set's type
   `_r' is the as-was type that we're throwing away.)
  Haskell currently supports changing the type of the record.
  (SPJ doubts whether type-changing has ever been a valuable feature.
   So do I.)

- Do you want to update Higher-rank fields?
  (typically used in records representing OO-style objects)
  Or is it enough to initialise the HR field when you create the record,
   then never change it?
  How many forall'd variables might you like in the HR field?

- Do you want to put constraints on the HR's forall'd types?

This is where the issue is stuck. Very possibly if we agree workable 
constraints, we're going to just run into further difficulties (like type 
inference becoming unmanageable without lots of type annotations to help 
resolve instances).

AntC



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


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution -record update

2012-02-09 Thread Donn Cave
Quoth AntC anthony_clay...@clear.net.nz,
...
 No, Donn, it's not the lack of syntax, it's the lack of semantics for first-
 class (polymorphic) record update. And there's very little that's obvious.

Ah, you're right, I certainly shouldn't have used the word syntax there.
But just to be clear on the point, I wonder if you could expand on what
you mean by polymorphic above.

I mean, when I wrote

  modifyRecord :: RecordType r = (a - a) - (r - a) - r - r

... while this does obviously represent a polymorphic function,
if I write

  data Config { tempo :: Int, ...}
  f = modifyRecord tempo (+20)

... then f has type Config - Config, it isn't polymorphic.
I am however vaguely aware that some parties to the Record
Question would like to make record fields themselves polymorphic, so
that 'tempo' could be defined for multiple record types and 'f'
would, I suppose, have a type like  RecordThatHasTempo r = r - r

Maybe that's semantically more like overloading, but in any case,
it isn't strictly necessary in order to support first class updates,
true?

Donn

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


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution -record update

2012-02-09 Thread AntC
Donn Cave donn at avvanta.com writes:

 
 
 --  modifyRecord :: RecordType r = (a - a) - (r - a) - r - r
modifyRecord :: RecordType r = (r - a) - (a - a) - r - r
 
 ... while this does obviously represent a polymorphic function,
Exactly!
 if I write
 
 --  data Config { tempo :: Int, ...}
data Config = Config { tempo :: Int, ...}
   f = modifyRecord tempo (+20)
   ...

But f defined like that is exactly what you can't write now (even with the 
args round the same way as the signature ;-), because:
* `tempo' is a function to select a field out of a record, *and only that*.
  So there's no way in the body of modifyRecord to use its (r - a)
  argument to put the updated `a' back into `r'.
* You can't (in current Haskell) put in place of `tempo' any type/species
  of a term that could achieve that update, except by either:
  making modifyRecord in effect monomorphic to Config/tempo,
  or building a polymorphic update system wot we 'ave no' go' (yet).

 ... then f has type Config - Config, it isn't polymorphic.
You can do:
f Config{ tempo, .. } = Config {tempo = tempo + 20, ..}
And that does yield f :: Config - Config

(But I'm sure you knew that.)

OK, we could implement lenses, make `tempo' a lens instead of a selector, 
desugar the update syntax to call the update 'method' out of the lens, ...
And of course somehow arrange the sugar that when `tempo' appears in other 
contexts we take the select 'method'.

You write up the proposal, and think through all the changes it would involve 
over Haskell/GHC as is, and then we can compare it to all those other 
proposals.

I think you'll still find you run into exactly the same difficulties I 
mentioned around update for record changing, Higher-ranked, etc.


 I am however vaguely aware that some parties to the Record
 Question would like to make record fields themselves polymorphic,
 
Yes, for example Jonathan Geddes' post:
 setName n r = r {name = n}
 addMr r = r { name = Mr.  ++ (name r) }

(Jonathan's post is asking for alternative syntax: that's rather ambitious 
when we can't yet write anything like that currently, indeed we don't even 
know how we could implement it in general.)

His context is, presumably, having lots of different record types all with a 
field `name'. (Arguably he should adopt long_and_meaningful_names for his 
various fields.)

 Maybe that's semantically more like overloading,

Yes, I've implemented it as overloading.

 but in any case,
 it isn't strictly necessary in order to support first class updates,
 true?
 
   Donn
 
Well, I think we might be getting stuck here with what does 'first class 
update' mean?

The narrow issue we're trying to address is namespacing, and specifically name 
clashes: two different records with the same named field.

I can't do better than quote SPJ again, sorry (not very) to repeat myself:
 SPJ in the SORF proposal asks:
 what does e { x = True } mean if there are lots of x fields in scope?
 (which is precisely what we want to allow)

It's true that each x is monomorphic (in the sense of being tied to a 
specific record and field type), but at the time the compiler encounters that 
expression, it doesn't know the type of `e'. (In general, `e' is some 
arbitrary expression -- perhaps selecting a record out of a keyed array?)

So the compiler relies on the name x being monomorphic to tell it. In 
contrast, -XDisambiguateRecordFields copes with different xs by insisting 
you put the Record's data constructor in place of the expression `e'.

If we want to turn this into a syntax question, we perhaps need a way of 
putting both an expression and a data constructor in with the field and the 
value to update. But note that the x in { x = True } is sort of hard-coded, 
there's currently no way to put an expression in its place.

So you still can't define a modifyConfig: you couldn't put anything in place 
of its (r - a) parameter that could represent x.

Now in return for me answering that, please answer the questions in my earlier 
post about what limitations on update you'd like:
* record-type changing?
* Higher-ranked fields?
* How many forall'd variables?
* Constrained forall'd variables?

Thank you
AntC


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


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution -record update

2012-02-09 Thread Donn Cave
Quoth AntC anthony_clay...@clear.net.nz,
 Donn Cave donn at avvanta.com writes:
...
 The narrow issue we're trying to address is namespacing, and specifically name
 clashes: two different records with the same named field.
...
 Now in return for me answering that, please answer the questions in my earlier
 post about what limitations on update you'd like:
 * record-type changing?
 * Higher-ranked fields?
 * How many forall'd variables?
 * Constrained forall'd variables?

All right, but it won't be a very interesting answer;  partly because
I personally do not find the name clash issue per se as compelling as
some - I mean, it can be a nuisance for sure, but it isn't broken the
way update per se is broken - and partly because, as best as I can
make out, I have never dreamed of using any of those four features.
So I hope someone with more invested in the problem will chime in!

Donn

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