Overloaded record fields

Carter Schonwald carter.schonwald at gmail.com
Sun Jun 30 08:06:15 CEST 2013


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.devriese at 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 <simonpj at 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-bounces at haskell.org [mailto:
> glasgow-haskell-
> > | users-bounces at haskell.org] On Behalf Of AntC
> > | Sent: 27 June 2013 13:37
> > | To: glasgow-haskell-users at haskell.org
> > | Subject: Re: Overloaded record fields
> > |
> > | >
> > | > ... 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 at haskell.org
> > | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> > _______________________________________________
> > Glasgow-haskell-users mailing list
> > Glasgow-haskell-users at haskell.org
> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20130630/e29c43f0/attachment.htm>


More information about the Glasgow-haskell-users mailing list