Re: Overloaded record fields

2013-06-30 Thread Carter Schonwald
at the risk of contributing to this bike shedding discussion, I'd like to
chime in:

Lets not break compose.

Also: why not something nearly as simple that ISN'T used already, eg (.$)
operator or something? (.) has enough overloading of what it can mean
already!  Now we have that (.) means 3 *completely* different things when
we do A.f ,  A . f , and  a.f !  So we have
an unprincipled conflation of *different* syntactic and semantic things,
and no deep reason for this aside from cause its what everyone else does.

Also unaddressed is how error messages for type and syntax will need to be
changed to handle any ambiguities that arise! Such engineering is beyond
the scope of whats feasible in a single summer I think... would it not be
better to choose an operator that *does not* create a potential conflation
with extant standard infix operators and qualified names?

Consider a strawman of (.$), which also doesn't not result in any syntactic
ambiguity, AND reuses familiar notational conventions of compose apply
AND resembles the conventional field accessor, AND to the best of my
knowledge isn't used in any current major libraries on hackage. (a quick
search with hayoo/holumbus indicates only one package on hackage, that
hasn't been touched in 5+ years has that infix operation)

Lets just give the darn field application its own function! $ reads as
apply, why not .$ for field apply?  Lets just make this
a first class operation that has highest precedence!

eg
(.$)::   r -(r { fieldName ::b } = r-b)-b
(.$) rec fun = --- stuff here

Summary:
Lets not make a wide spread syntactic element MORE Confusing. Please. Also
as explained by others, it will break Lens which is now a *very* widely
used library by many in the community. Theres no good reason. At all.

I welcome an explanation that motivates the . dot syntax and all the extra
ghc flag hoops people are bikeshedding around that are necessitated by the
syntactic tomfoolery, but I can not imagine any good reason aside from
people's feelings and the inertia of opinions already developed.


cheers, either way, i'm excited about the prospect of making it easier to
write Symbol Singletons more easily as a result of the more *important*
elements of this work.

-Carter




On Fri, Jun 28, 2013 at 11:48 AM, Dominique Devriese 
dominique.devri...@cs.kuleuven.be wrote:

 Simon,

 I see your point.  Essentially, the original proposal keeps the
 namespace for field names syntactically distinguishable from that of
 functions, so that the type given to r.foo doesn't depend on what is
 in scope.  (.foo) is always defined and it is always a function of
 type (r { foo::t }) = r - t. With the orthogonal proposal, it
 would only be defined if there is a record with a foo field in scope,
 although its definition or type does not actually depend on the
 record.   One would then need to define an Unused record with a field
 foo, or declare the following
   foo :: r { foo ::t} = r - t
   foo = getFld
 to essentially declare that foo should be treated as a field selector
 and I'm not even sure if type inference would work for this
 definition... Maybe we could provide syntax like a declaration field
 foo; as equivalent to the latter, but I have to acknowledge that this
 is a downside for the orthogonal proposal.

 Regards,
 Dominique

 2013/6/28 Simon Peyton-Jones simo...@microsoft.com:
  | Folks, I'm keenly aware that GSoC has a limited timespan; and that
 there
  | has already been much heat generated on the records debate.
 
  I am also keenly aware of this.  I think the plan Ant outlines below
 makes sense; I'll work on it with Adam.
 
  I have, however, realised why I liked the dot idea.  Consider
 
  f r b = r.foo  b
 
  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
 
  * If there are no records in scope with field foo
and no other foo's, the program is rejected
 
  * If there are no records in scope with field foo
but there is a function foo, then the usual thing happens.
 
  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.
 
  I wanted to jot this point down, but I think it's a lesser evil than
 falling into the dot-notation swamp.  After all, it must be vanishingly
 rare to write a function manipulating foo fields when there are no such
 records around. It's just a point to note (NB Adam: design document).
 
  Simon
 
  | -Original Message-
  | From: glasgow-haskell-users-boun...@haskell.org [mailto:
 glasgow-haskell-
  | users-boun...@haskell.org] On Behalf Of AntC
  | Sent: 27 June 2013 13:37
  | To: glasgow-haskell-users@haskell.org
  | 

A possible alternative to dot notation for record access

2013-06-30 Thread Judah Jacobson
 Hi all,

I had a quick idea about record field syntax as specified in the GSoC
project plan:
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Plan
.

Instead of f.x (to access field x of record f), maybe we could write
f{x} as the record selection.  That is, we'd reuse the brace notation
which is already in place for record updates.  Unlike dot notation, this is
unambiguous and doesn't conflict with any existing syntax (AFAIK).  It
would also generalize to f{x}{y}{z} instead of f.x.y.z.

This proposal would add two new forms of expressions:

f{x} to access field x of data f
({x}) = \f - f{x} as a field access section

Additionally, it seems like record mutation expressions could also have
sections:

({x=2}) = \f - f{x=2}

That actually seems useful by itself, regardless of whether we use dot
notation for field access.

Best,
-Judah
___
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 Carter Schonwald
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
.

Otoh, would there be any ambiguity wrt applying functions to blocks?


eg
f = (+ 1)
h= f {let x = 7 in 3*x},
would that trip up the syntax?




On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson judah.jacob...@gmail.comwrote:

 Hi all,

 I had a quick idea about record field syntax as specified in the GSoC
 project plan:
 http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Plan
 .

 Instead of f.x (to access field x of record f), maybe we could write
 f{x} as the record selection.  That is, we'd reuse the brace notation
 which is already in place for record updates.  Unlike dot notation, this is
 unambiguous and doesn't conflict with any existing syntax (AFAIK).  It
 would also generalize to f{x}{y}{z} instead of f.x.y.z.

 This proposal would add two new forms of expressions:

 f{x} to access field x of data f
 ({x}) = \f - f{x} as a field access section

 Additionally, it seems like record mutation expressions could also have
 sections:

 ({x=2}) = \f - f{x=2}

 That actually seems useful by itself, regardless of whether we use dot
 notation for field access.

 Best,
 -Judah

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


___
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 Roman Cheplyaka
* Carter Schonwald carter.schonw...@gmail.com [2013-06-30 03:26:22-0400]
 Otoh, would there be any ambiguity wrt applying functions to blocks?
 
 eg
 f = (+ 1)
 h= f {let x = 7 in 3*x},
 would that trip up the syntax?

This is not valid Haskell anyway (there's no such thing as applying
functions to blocks). You can write

  h = f (let {x = 7} in 3*x)

or

  h = f $ let {x = 7} in 3*x

Roman

 On Sun, Jun 30, 2013 at 2:59 AM, Judah Jacobson 
 judah.jacob...@gmail.comwrote:
 
  Hi all,
 
  I had a quick idea about record field syntax as specified in the GSoC
  project plan:
  http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Plan
  .
 
  Instead of f.x (to access field x of record f), maybe we could write
  f{x} as the record selection.  That is, we'd reuse the brace notation
  which is already in place for record updates.  Unlike dot notation, this is
  unambiguous and doesn't conflict with any existing syntax (AFAIK).  It
  would also generalize to f{x}{y}{z} instead of f.x.y.z.
 
  This proposal would add two new forms of expressions:
 
  f{x} to access field x of data f
  ({x}) = \f - f{x} as a field access section
 
  Additionally, it seems like record mutation expressions could also have
  sections:
 
  ({x=2}) = \f - f{x=2}
 
  That actually seems useful by itself, regardless of whether we use dot
  notation for field access.
 
  Best,
  -Judah
 
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
 

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


___
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 Ben Franksen
Judah Jacobson wrote:
 I had a quick idea about record field syntax as specified in the GSoC
 project plan:
 
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Plan
 .
 
 Instead of f.x (to access field x of record f), maybe we could write
 f{x} as the record selection.  That is, we'd reuse the brace notation
 which is already in place for record updates.  Unlike dot notation, this 
is
 unambiguous and doesn't conflict with any existing syntax (AFAIK).  It
 would also generalize to f{x}{y}{z} instead of f.x.y.z.
 
 This proposal would add two new forms of expressions:
 
 f{x} to access field x of data f
 ({x}) = \f - f{x} as a field access section
 
 Additionally, it seems like record mutation expressions could also have
 sections:
 
 ({x=2}) = \f - f{x=2}
 
 That actually seems useful by itself, regardless of whether we use dot
 notation for field access.

I think this is a pretty nice idea. (Disclaimer: I haven't spent any time on 
checking corner cases; also I firmly belong to the anti-further-overloading-
of-dot faction). In any case it is light-weight enough to be actually 
useful, it is readable and suggestive, and (at least conceptually) fits well 
in the existing record syntax.

This deserves a fully fleshed-out proposal for Haskell' IMO.

Cheers
-- 
Ben Franksen
()  ascii ribbon campaign - against html e-mail 
/\  www.asciiribbon.org   - against proprietary attachm€nts


___
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: A possible alternative to dot notation for record access

2013-06-30 Thread amindfv
As long as we're bikeshedding...

Possibly '#' is unused syntax -- Erlang uses it for its records too, so we 
wouldn't be pulling it out of thin air. E.g. person#firstName

Tom


El Jun 30, 2013, a las 22:59, AntC anthony_clay...@clear.net.nz escribió:

 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

___
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 Edward Kmett
(#) is a legal operator today and is used in a number of libraries.

On Sun, Jun 30, 2013 at 11:38 PM, amin...@gmail.com wrote:

 As long as we're bikeshedding...

 Possibly '#' is unused syntax -- Erlang uses it for its records too, so we
 wouldn't be pulling it out of thin air. E.g. person#firstName

 Tom


 El Jun 30, 2013, a las 22:59, AntC anthony_clay...@clear.net.nz
 escribió:

  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

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

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