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

On 1/02/2012, at 11:38 AM, AntC wrote:
As soon as you decide to make 'virtual record selectors' just ordinary functions (so they select but not update) , then you can see that field names are also just ordinary functions (for selection purposes). So the semantics for field 'selection' (whether or not you use dot notation) is just function application. So Type-Directed Name resolution is just instance resolution. So it all gets much easier.
Richard O'Keefe wrote: ... Making f x and x.f the same is pretty appealing, but it is imaginable that the former might require importing the name of f from a module and the latter might not. That is to say, it lets f and .f have completely different meanings. Oh the joy! Oh the improved readability! -- on some other planet, maybe.
Hi Richard, I'm not sure I understand what you're saying. I'm proposing x.f is _exactly_ f x. That is, the x.f gets desugared at an early phase in compilation. If the one needs importing some name from a module, than so does the other. A 'one-sided dot doesn't mean anything. (Also, I feel vaguely nauseous even seeing it written down.) Under my proposal, the only thing .f could mean is: \z -> z.f which desugars to \z -> f z which means (by eta-reduction) f And to complete the story: the only thing (x.) could mean is: \g -> x.g So a use like: (x.) f -- or z f, where z = (x.) would desugar to f x which is the same as x.f A use like (x.)f (no spaces around the parens) would amount to the same thing. This is all so weird I'm inclined to say that one-sided dot is probably a syntax error, and reject it. It's too dangerously ambiguous between the syntax for 'proper' dot notation and function composition. Or is there something I'm not understanding? [Good to see another NZ'er on the list, by the way.] AntC

On Tue, 31 Jan 2012 23:10:34 -0700, Anthony Clayden
I'm proposing x.f is _exactly_ f x. That is, the x.f gets desugared at an early phase in compilation.
Anthony, I think part of the concern people are expressing here is that the above would imply the ability to use point-free style. But this orthogonality is disavowed by your exception:
A 'one-sided dot doesn't mean anything.
I haven't read the underlying proposals, so I apologize if the following is covered, but my understanding of the discussion is that the x.f notation is intended to disambiguate f to be a field name of the type of x and therefore be advantageous over "f x" notation where f is presently in the global namespace. With your exception, I still cannot disambiguate the following: data Rec = { foo :: String } foo :: Rec -> String foo = show rs :: [Rec] rs = [ ... ] bar = map foo rs If the exception doesn't exist, then I could write one of the following to clarify my intent: bar = map foo rs baz = map .foo rs -- -KQ

Kevin Quick
On Tue, 31 Jan 2012 23:10:34 -0700, Anthony Clayden
wrote: I'm proposing x.f is _exactly_ f x. That is, the x.f gets desugared at an early phase in compilation.
Anthony,
I think part of the concern people are expressing here is that the above would imply the ability to use point-free style. But this orthogonality is disavowed by your exception:
A 'one-sided dot doesn't mean anything.
Kevin, thank you for helping me clarify my descriptions. I admit my 'proposal' is probably a bit hard to follow at the moment, because it lives in a series of emails, rather than all in a coherent wiki page. It's also possibly confusing because there are three differing proposals in play, and they all use dot notation for field selection, but they use it somewhat differently. But every proposal supports dot-as-function-composition, providing the dot appears with space on both sides. The discussion with Donn Cave has clarified that under my proposal (but not TDNR or SORF), the dot notation is not necessary. Donn is concerned that older code might be using dot for function composition in contexts that would be ambiguous with field-selection-as-reverse-application. http://www.haskell.org/pipermail/haskell-cafe/2012-January/099008.html So we could make the dot notation a compiler option: - you either keep with H98 syntax, so field selection must be by usual function syntax f x - or use dot notation so that x.f desugars to f x (of course you could still use f x: nothing forces you to use the dot) Let me give some examples to clarify what I mean by 'one-sided' dot: M.f -- no spaces, upper case to left, is qualified name x.f -- no spaces, lower case to left, desugars to f x x . f -- spaces both side of dot, is function composition x. f -- space on one side only, what does that mean? x .f -- space on one side only, what does that mean? In my view, those last two (which I'm calling 'one-sided' dot) are too confusing (for the eye, at least). I would reject them as invalid syntax. H98 might treat them as function composition. (I'm not sure, I wouldn't code like that.) Donn is saying that he doesn't want to break extant code that uses 'one-sided' dot. Fair enough. Under my proposal we could make it a compiler option to stick with H98 syntax, an which case x.f is function composition (I believe), not field selection. I know Wadler's rule about the disproportionate time spent on lexical syntax. SPJ was trying (inter alia) to introduce dot notation to support more OO-type thinking. I'm more familiar with dot-as-field-selector from relational databases, so I'm keen to introduce it. But frankly it's a side-show compared to addressing the namespace issues around records.
I haven't read the underlying proposals, ...
No, clearly you haven't from what follows. Pay me (and the other contributors) the respect of doing so before wasting my time. I'm a busy person. I appreciate the feedback on this forum when it's informed. I appreciate that people give their time voluntarily (which is what I'm doing).

Fair deuce. With all due respect now included, my same concern still seems to
apply although I believe I poorly stated it originally. Allow me to retry:
By declaring partial application an invalid parse, it introduces an exception
to point-free style that is at odds with the normal intuition of the uses of "f x".
SPJ's SOPR raises it as an issue and indicates he's inclined to disallow it; my
concern above would still apply.
As I surely mis-understand it (referencing your proposal as RHCT since I haven't
seen another reference):
SOPR: map (\r -> f r) recs
SOPR: map (get f) recs
SOPR/alt: qfmap (undefined :: "f") id recs
RHCT: map (\r -> f r) recs
RHCT: map (\r -> r.$rev_ f) recs
RHCT: map ((.$)f) recs
If partial application is allowed (against SPJ's inclination and explicitly
disallowed in your scheme), I could have:
map .f recs
in either SOPR or your proposal, which (to me) is an intuitive coordination of
the two concepts (point-free/partial application and f.x desugaring). I don't
think this is currently a valid parse, so I don't think it breaks existing, but
that's not a very well informed opinion either.
My concern is a triviality however; my intent was to attempt to assist in trying
to clarify a what I perceived as a conceptual gap in the discussion. I am most
grateful for the significant time and effort contributed by yourself, SPJ, and
all other parties, and I fear I've mostly wasted people's time on syntactic
trivialities already well discussed and dismissed. Please do carry on, it's all
good stuff.
-KQ
Quoting AntC
Kevin Quick
writes: On Tue, 31 Jan 2012 23:10:34 -0700, Anthony Clayden
wrote: I'm proposing x.f is _exactly_ f x. That is, the x.f gets desugared at an early phase in compilation.
Anthony,
I think part of the concern people are expressing here is that the above would imply the ability to use point-free style. But this orthogonality is disavowed by your exception:
A 'one-sided dot doesn't mean anything.
Kevin, thank you for helping me clarify my descriptions. I admit my 'proposal' is probably a bit hard to follow at the moment, because it lives in a series
of emails, rather than all in a coherent wiki page.
It's also possibly confusing because there are three differing proposals in play, and they all use dot notation for field selection, but they use it somewhat differently.
But every proposal supports dot-as-function-composition, providing the dot appears with space on both sides.
The discussion with Donn Cave has clarified that under my proposal (but not TDNR or SORF), the dot notation is not necessary. Donn is concerned that older code might be using dot for function composition in contexts that would be ambiguous with field-selection-as-reverse-application. http://www.haskell.org/pipermail/haskell-cafe/2012-January/099008.html
So we could make the dot notation a compiler option: - you either keep with H98 syntax, so field selection must be by usual function syntax f x - or use dot notation so that x.f desugars to f x (of course you could still use f x: nothing forces you to use the dot)
Let me give some examples to clarify what I mean by 'one-sided' dot: M.f -- no spaces, upper case to left, is qualified name x.f -- no spaces, lower case to left, desugars to f x x . f -- spaces both side of dot, is function composition x. f -- space on one side only, what does that mean? x .f -- space on one side only, what does that mean?
In my view, those last two (which I'm calling 'one-sided' dot) are too confusing (for the eye, at least). I would reject them as invalid syntax. H98
might treat them as function composition. (I'm not sure, I wouldn't code like
that.)
Donn is saying that he doesn't want to break extant code that uses 'one-sided' dot. Fair enough. Under my proposal we could make it a compiler option to stick with H98 syntax, an which case x.f is function composition (I believe),
not field selection.
I know Wadler's rule about the disproportionate time spent on lexical syntax.
SPJ was trying (inter alia) to introduce dot notation to support more OO-type
thinking. I'm more familiar with dot-as-field-selector from relational databases, so I'm keen to introduce it.
But frankly it's a side-show compared to addressing the namespace issues around records.
I haven't read the underlying proposals, ...
No, clearly you haven't from what follows. Pay me (and the other contributors) the respect of doing so before wasting my time. I'm a busy person. I appreciate the feedback on this forum when it's informed. I appreciate that people give their time voluntarily (which is what I'm doing).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------------------------------------------- This mail sent through IMP: http://horde.org/imp/

Fair deuce. With all due respect now included, my same concern still seems
to
apply although I believe I poorly stated it originally. Allow me to retry: OK, thank you.
By declaring partial application an invalid parse, it introduces an
exception
to point-free style that is at odds with the normal intuition of the uses of "f x".
I'm not (and I don't think any of the other proposals are) trying to declare partial application as an invalid parse. I'm saying that if you want to part- apply function composition (in point-free style), you need to be careful with your syntax, because it's easily confused. A piece of background which has perhaps been implicit in the discussions up to now. Currently under H98: f.g -- (both lower case, no space around the dot) Is taken as function composition -- same as (f . g). f. g -- is taken as func composition (f . g) f .g -- is taken as func composition (f . g) I believe all three forms are deprecated these days, but as Donn points out there may be code still using it. Part of the reason for deprecating is the qualified name syntax, which _mustn't_ have dots. So: M.f -- is qualified f from module M M. f -- is dubious, did you mean M.f? -- or function composition (M . f)? -- with M being a data constructor M .f -- similarly dubious between M.f vs (M . f) The reason those are dubious is that it's relatively unusual to part-apply a data constructor in combination with function composition. More likely you've made a typo. Nevertheless, if that's what you want to do, be careful to code it as (M . f) All the proposals in play are going to change the meaning of f.g. Some of the proposals (not mine) are going to change the meaning of f. and /or .g -- as Donn points out, any/all of these changes may break code. I say it's better to be conservative: reject f. and .g as invalid syntax. (If existing code has f.g as function composition, changing the meaning to field extraction is going to give a type failure, so it'll be 'in your face'.) All proposals are saying that if you want to use dot as function composition you must always put the spaces round the dot (or at least between the dot and any name) -- even if you're part-applying. So: (f .) -- part-apply function composition on f (. g) -- part-apply function composition {- as an exercise for the reader: what does that second one mean? How is it different to the first one? Give an example of use with functions head, tail and a list. -} (f.) -- I say is ambiguous, did you mean (f .) -- or miss out something after the dot ? (.f) -- I say is ambiguous, did you mean (. f) -- or miss out something before the dot ? I'm saying that for both of the above, it's safer to treat them as an invalid parse, and require a space between the dot and the name.
SPJ's SOPR raises it as an issue and indicates he's inclined to disallow it;
my
concern above would still apply.
"SOPR"? SPJ's current proposal is abbreviated as "SORF" (Simple Overloaded Record Fields). His older proposal as "TDNR" (Type-Directed Name Resolution). http://hackage.haskell.org/trac/ghc/wiki/Records I don't think either of those disallow partial application of function composition. I do think they discuss how the syntax could be confusing, so require you to be careful. Another piece of background which the discussion is probably not being explicit about (so thank you for forcing me to think through the explanation): under H98 record declarations data Customer = Customer { customer_id :: Int } You immediately get a function: customer_id :: Customer -> Int Then you can apply customer_id to a record, to extract the field. Because the type of customer_id is restricted to exactly one record type, this strengthens type inference. (Whatever customer_id is applied to must be type Customer, the result must be type Int.) For my proposal, I'm trying very hard to be consistent with the H98 style, except to say that field extractor function f can apply to any record type (providing it has field f). Specifically, if the f field is always a String, we can help type inference. The type of f is (approximately speaking): f :: (Has r Proxy_f String) => r -> String Or I prefer SPJ's suggested syntactic sugar: f :: r{ f :: String} => r -> String But type inference for r is now harder: we have to gather information about r from the type environment where f is applied to r, enough to figure out which record type it is; then look up the instance declaration (generated from the data decl) to know how to extract the f field. That much isn't too hard. The really difficult part is how to do that in such a way that we can also update f to produce a new r, and cope with all the possible things f might be - including if f is polymorphic or higher-ranked. (The "trying hard" is why my Record Update for Higher-ranked or Changing Types contained such ugly code.) So I'm trying to support mixing H98 record fields with new-style poly-record field extractors. If you see in code: f r (And you know already that r is a record and f is a field -- perhaps you're working in a database application). Then you know we're extracting a field from a record, whether it's a H98 record or a new-style record. Similarly: r.f -- desugars to f r, so you know just as much What's more, perhaps you've got new-style records in your module, but you're importing a H98 record definition from some other module. Then: customer_id customer -- extracts the customer_id from the record customer.customer_id -- means just the same Wow!! we've just used dot-notation on H98-style records, and we didn't need to change any code at all in the imported module.
As I surely mis-understand it (referencing your proposal as RHCT since I
haven't
seen another reference):
You're right that there isn't a name for my proposal, and I definitely need one. (I take it "RHCT" comes from Record Update for Higher-ranked or Changing Types. Doesn't quite trip off the tongue, I'd say.) I'm thinking: "DORF" -- Declared Overloaded Record Fields -- The "ORF" part is similar to SPJ's SORF. -- The "Declared" means you have to declare a field, -- before using it in a data decl. -- Or the "D" might mean "Dictionary-based" as in data dictionary -- (not "dictionary" in the sense of "dictionary-passing") In these examples you're giving, I assume recs is a list of records(?). I don't understand what you're doing with the "SOPR" items, so I've cut them.
...
In the "RHCT" examples, I assume r is a record, f is a field (selector function) -- or is it 'just some function'?, rev_ is a field selector for a higher-ranked function (to reverse lists of arbitrary type), .$ is the 'fake' I used to simulate dot-as-field-selector. Thank you for reading all that so closely.
RHCT: map (\r -> f r) recs is the same as: map f recs -- by eta reduction so map f takes a list of records, returns a list of the f field from each This also works under H98 record fields, with type enforcement that the records must be of the single type f comes from.
RHCT: map (\r -> r.$rev_ f) recs Beware that (.$) is an operator, so it binds less tightly than function application, so it's a poor 'fake' syntactically. Did you mean .$ to simulate dot-notation to extract field rev_ from r? Then put: map (\r -> (r.$rev_) f) recs This takes the Higher-Ranked reversing function from each record in recs, and (on the face of it) returns a list obtained by applying it to f. I've assumed above that f is a field selector function (or 'just some function'). So it's not a list. So you'll get a type error trying to apply (r.$rev_) to f.
If you meant to apply (r.$rev_) to the f field in r, put: map (\r -> (r.$rev_) (r.$f)) recs For the type to work, this requires the f field to be a list. The map returns a list of reversed lists from the f field of each record.
RHCT: map ((.$)f) recs If you mean this to return a list of the f fields from recs, put: map f recs I don't know what else you could be trying to do.
If partial application is allowed (against SPJ's inclination and explicitly disallowed in your scheme), I could have:
map .f recs
If you mean this to return a list of the f fields from recs, put: DORF: map f recs -- are you beginning to see how easy this is? I'm saying the ".f" should be rejected as too confusing. (That is, under DORF aka RHCT. Under SORF or TDNR I'm not sure, which is why I don't like their proposals for dot notation, which is why I re-engineered it so that dot notation is tight-binding reverse function application **and nothing more**.) I don't know what else you could be trying to do, but if you're trying to use dot as function composition (part-applied), put: map (. f) recs But this won't extract an f field from recs (exercise for the reader).
... my intent was to attempt to assist in trying to clarify a what I perceived as a conceptual gap in the discussion. I am most grateful for the significant time and effort contributed by yourself, SPJ, and all other parties, and I fear I've mostly wasted people's time on syntactic trivialities already well discussed and dismissed. Please do carry on, it's all good stuff.
-KQ
Thank you Kevin, we got there in the end. Your questions did help me clarify and explain what was implicit. I think in general that syntax is trivial, but for one thing we've got very complex syntax already in Haskell. Our 'syntax engineering' has got to be careful to 'fit in', and not use up too many of the options that are still available. What's special with dot syntax is it's well-established and with well- established (range of) meanings in other programming paradigms. If we introduce dot-notation into Haskell, we have to try to make it behave like those paradigms, but in a 'Haskelly' way. [To go a little off-topic/out of scope. My gold standard is polymorphic/anonymous records with concatenation, merge, projection, extension, everything you get in relational algebra. I don't want to use up all the design options just getting through the current namespace restrictions -- infuriating though they are.] AntC

On Wed, 01 Feb 2012 19:42:19 -0700, AntC
A piece of background which has perhaps been implicit in the discussions up to now. Currently under H98: f.g -- (both lower case, no space around the dot) Is taken as function composition -- same as (f . g). f. g -- is taken as func composition (f . g) f .g -- is taken as func composition (f . g)
And so it is. Could have sworn these weren't accepted, but clearly I'm wrong. Thanks for pointing this out.
All proposals are saying that if you want to use dot as function composition you must always put the spaces round the dot (or at least between the dot and any name) -- even if you're part-applying. So: (f .) -- part-apply function composition on f (. g) -- part-apply function composition
+1
"SOPR"? SPJ's current proposal is abbreviated as "SORF" (Simple Overloaded Record Fields).
Yes, I caught this 5 minutes *after* hitting send (of course).
In these examples you're giving, I assume recs is a list of records(?).
Yes. I err'd on the side of brevity.
...
In the "RHCT" examples, I assume r is a record, f is a field (selector function) -- or is it 'just some function'?
It should be a field selector.
RHCT: map (\r -> f r) recs is the same as: map f recs -- by eta reduction so map f takes a list of records, returns a list of the f field from each This also works under H98 record fields, with type enforcement that the records must be of the single type f comes from.
RHCT: map (\r -> r.$rev_ f) recs Beware that (.$) is an operator, so it binds less tightly than function application, so it's a poor 'fake' syntactically. Did you mean .$ to simulate dot-notation to extract field rev_ from r?
Sort of. I didn't fully grasp your implemenation and based on your clarification I think I should have written: map (\r -> r.$f) recs to extract field f from a single record r (from the recs collection).
RHCT: map ((.$)f) recs If you mean this to return a list of the f fields from recs, put: map f recs I don't know what else you could be trying to do.
I was trying to eta-reduce my previous (corrected) situation *but* also indicate that I specifically want the field selector rather than some arbitrary f. I wanted to extract the field f of every record in recs but clearly indicate that f was a field selector and not a free function.
If partial application is allowed (against SPJ's inclination and explicitly disallowed in your scheme), I could have:
map .f recs
If you mean this to return a list of the f fields from recs, put: DORF: map f recs -- are you beginning to see how easy this is?
I'm saying the ".f" should be rejected as too confusing. (That is, under DORF aka RHCT. Under SORF or TDNR I'm not sure, which is why I don't like their proposals for dot notation, which is why I re-engineered it so that dot notation is tight-binding reverse function application **and nothing more**.)
And this is finally our difference. I had wanted the no-space preceeding dot syntax (.f) to specifically indicate I was selecting a field. This desire was based on expectations of partial application and being unaware of the H98 valid interpretation of this as partial function application. I think perhaps I was overly concerned on this point though. The issue can be resolved by explicit module namespace notation (ala. Prelude.map v.s. Data.List.map). In addition, under SORF, SPJ indicated that "Dot notation must work in cascades (left-associatively), and with an expression to the left: r.x r.x.y (foo v).y " I assume DORF would also support this as well and that "r.x.y.z" would desugar to "z (y (x r))". With regards to module namespace notation, neither SORF nor DORF mentions anything that I found, but I'm assuming that the assertion is that it's not needed because of the type-directed resolution. To wit: Rlib/Recdef.hs:
module Rlib.Recdef (R(..)) where
data Rec = R { foo :: String } deriving Show
Rlib/Rong.hs:
module Rong (T(..)) where import Rlib.Recdef data Rstuff = T { baz :: R }
foo :: Rec -> String foo = show
main.hs:
import Rlib.Recdef import Rlib.Rong main = let r = R "hi" t = T r bar, bar_pf :: Rstuff -> String bar_pf = Rlib.Recdef.foo . Rlib.Rong.baz bar x = x.baz.foo in assert $ bar_pf t == bar t assert $ Rlib.Rong.foo r /= Rlib.Recdef.foo r
The assumptions are that the syntax of bar and bar_pf would be the same for both SORF and DORF, and that no namespace qualifiers are needed (or allowed) for bar (i.e. you wouldn't write something like "bar x = x.Rlib.Rong.baz.Rlib.Recdef.foo"). Apologies for putting you through the syntax grinder, and especially when I'm not really qualified to be operating said grinder. I know it's not the interesting part of the work, but it's still a part. Thanks, Anthony! -Kevin -- -KQ

Kevin Quick
Currently under H98: f.g -- (both lower case, no space around the dot) Is taken as function composition -- same as (f . g). f. g -- is taken as func composition (f . g) f .g -- is taken as func composition (f . g)
And so it is. Could have sworn these weren't accepted, but clearly I'm wrong. Thanks for pointing this out.
On a bit more digging, I'm scaring myself. These are both valid (H98): Data.Char.toUpper.Prelude.head.Prelude.tail $ "hello" -- Strewth! "hello".$Prelude.tail.$Prelude.head.$Data.Char.toUpper -- using (.$) = flip ($) as fake dot notation GHCiorHugs==> 'E' The first example is good in that you can mix qualified names in with dot notation, and the lexer can bind the module name tighter than dot-as-function- composition. It's bad that not only are we proposing changing the meaning of dot, we're also changing the direction it binds. If you put in the parens: (Data.Char.toUpper.(Prelude.head.(Prelude.tail))) "hello" (("hello".$Prelude.tail).$Prelude.head).$Data.Char.toUpper Or perhaps not so bad, left-to-right thinking? Another syntax change about dot-notation is that it binds tighter **than even function application**: map toUpper customer.lastName Desugars to: map toUpper (lastName customer) Compare if that dot were function composition: (map toUpper customer) . lastName -- of course this isn't type-valid But wait! there's more! we can make it worse! A field selector is just a function, so I can select a field and apply a function all in one string of dots: customer.lastName.tail.head.toUpper -- Yay!!
I was trying to ... *but* also indicate that I specifically want the field selector rather than some arbitrary f. I wanted to extract the field f of every record in recs but clearly indicate that f was a field selector and not a free function.
And this is finally our difference. I had wanted the no-space preceeding dot syntax (.f) to specifically indicate I was selecting a field. ...
You seem to be not alone in wanting some special syntax for applying field selectors (see other posts on this thread). H98 field selectors don't do this, they're just functions. And there's me bending over backwards to make all Type-Directed overloaded- Name Resolution field selectors just functions, so you can mix field selectors and functions **without** special syntax. Example Yay!! above. I'm puzzled why you want different syntax for field selectors. Can you give some intuition? Of course you can adopt a convention in your own code that dot-notation is for field selection only. (But you can't legislate for code you're importing.) (And Donn Cave wants to be able to ignore dot notation all together.) AFAIC OO languages lets you put all sorts of weird stuff together with dot notation. SPJ's got an example from Java in his TDNR. I hope it's not because you name your fields and functions with brief, cryptic, one-letter codes!! You do have a coding convention in you production code to use long_and_meaningful_names, don't you?! So you can tell `customer' is a customer (record), and `lastName' is a last Name (field), etc.
The issue can be resolved by explicit module namespace notation (ala. Prelude.map v.s. Data.List.map).
I want module namespace notation **as well as** dot notation. This is my import from a distant planet example. And it'll work, going by example Strewth! above.
In addition, under SORF, SPJ indicated that "Dot notation must work in cascades (left-associatively), and with an expression to the left: r.x r.x.y (foo v).y " I assume DORF would also support this as well and that "r.x.y.z" would desugar to "z (y (x r))".
Yes, as per discussion above.
With regards to module namespace notation, neither SORF nor DORF mentions anything that I found, but I'm assuming that the assertion is that it's not needed because of the type-directed resolution.
It's rather the other way round. We want to avoid qualified names, and type- directed resolution is the mechanism to achieve that ... Where this 'Records in Haskell' thread started is that currently if you want to have the same field name in different records, you have to declare the records in different modules, then import them to the same place, and still you can only refer to them by putting the module prefix. (Unless you use the - XDisambiguateRecordFields flag, but this only works within the scope of pattern matches and explicit record/data constructors; it doesn't work for the free-floating selector functions.) And on balance, putting module prefixes everywhere is just too cumbersome. So yes, the plan with SORF and DORF is that you can (mostly) use un-qualified names, and the resolution mechanism figures out which record type you're talking about. One difference between DORF and SORF is that I want the resolution mechanism to be exactly class/instance resolution. In contrast, both SORF and TDNR want some special syntax-level resolution for dot-notation, at the desugaring stage. I've re-read those sections in both proposals, and I still don't 'get' it. That's again what prompted me to try harder. I think I've ended up with an approach that's more 'Haskelly' in that the field selector is just an overloaded function, and we're familiar with them, and how they get resolved through type/instance inference. [I've just re- read that last sentence: I'm claiming to be more 'Haskelly' than SPJ!! The arrogance!] There's one further difference between DORF and SORF/TDNR. I'm explicit about this, but I'm not sure what SORF's take is. I think SORF/TDNR keeps with current Haskell that you can't declare more than one record with the same field name in the same module. I want to declare many records in the same module with the same field name(s). This is my customer_id example: All three of the records for customer Name/Address, customer pricing, and customer orders have a customer_id field.
To wit:
Rlib/Recdef.hs:
module Rlib.Recdef (R(..)) where
data Rec = R { foo :: String } deriving Show
Rlib/Rong.hs:
module Rong (T(..)) where import Rlib.Recdef data Rstuff = T { baz :: R }
foo :: Rec -> String foo = show
main.hs:
import Rlib.Recdef import Rlib.Rong main = let r = R "hi" t = T r bar, bar_pf :: Rstuff -> String bar_pf = Rlib.Recdef.foo . Rlib.Rong.baz bar x = x.baz.foo in assert $ bar_pf t == bar t assert $ Rlib.Rong.foo r /= Rlib.Recdef.foo r
The assumptions are that the syntax of bar and bar_pf would be the same for both SORF and DORF, and that no namespace qualifiers are needed (or allowed) for bar (i.e. you wouldn't write something like "bar x = x.Rlib.Rong.baz.Rlib.Recdef.foo").
This isn't really demonstrating the point. Both definitions of foo are monomorphic Rec -> String, there's no type-level difference. It's _not_ an overloaded definition of a single foo, it's a clash of names declared in different modules. So to tell them apart within the same scope, you always need the module qualifier. The use of foo embedded in bar_pf is qualified, so bar_pf will always show the foo field within the record ("hi"). The foo in bar is not qualified. I'd expect the compiler to complain that it's ambigous. (Looks like that's valid code today, if you change bar's RHS to x.$baz.$foo -- did you try it?) And no, you can't concoct an example today that demonstrates DORF, because record Rec automatically declares function foo with a monomorphic type. You'll have to create some shadow field/functions (foo_, _foo, Proxy_foo, the Has instance and all the drama) as I did in the RHCT post.
Apologies for putting you through the syntax grinder, and especially when I'm not really qualified to be operating said grinder. I know it's not the interesting part of the work, but it's still a part.
Thanks, Anthony!
-Kevin
Cheers Anthony

On Fri, Feb 3, 2012 at 10:30 AM, AntC
You seem to be not alone in wanting some special syntax for applying field selectors (see other posts on this thread). H98 field selectors don't do this, they're just functions.
And there's me bending over backwards to make all Type-Directed overloaded- Name Resolution field selectors just functions, so you can mix field selectors and functions **without** special syntax. Example Yay!! above.
I'm puzzled why you want different syntax for field selectors. Can you give some intuition?
Here's my problems with allowing postfix application using dot for all functions. The first problem is that mixing prefix and postfix function application within the same line makes it harder to read. When you read code to try to understand what it does, the direction you like to go in is "here's some object, first do this to it, then do that to it, then do this other thing to it, then this fourth thing to produce the final result". In Haskell code with prefix application, this is easy: you read it from right to left. In OO-style code using dots, it's even easier: you read it from left to right. But if you mix the two, it's much harder than either: you first have to figure out where the sentence even begins, which is going to be somewhere in the middle, and then every time the expression switches between prefix and postfix, you have to figure out where to continue reading. The algorithm your brain needs to follow is a lot branchier, so to speak. This is the smaller problem. If prefix and postfix notations are completely interchangeable, then we can at least expect people to not make their own code hard to read, and to stick to one or the other within an expression. (If they're *not* interchangeable, and one or the other is required in some cases, then it's a bigger problem.) The other problem is that, in order to make partial application convenient, you want to put your function's parameters in the order of least specific to most specific. If you want to make postfix application convenient, you have to do the reverse. For example, take the filter function from the Prelude: filter :: (a -> Bool) -> [a] -> [a] The order of its parameters makes it easy to write specialized filter functions by partially applying filter, for example: filterEvens = filter even This is convenient and useful. (It's even more useful within expressions, when you want to pass a function as an argument to a higher-order function, which happens very frequently.) By contrast, it's not usually useful to be able to specialize filter by the list it filters, which is what you could conveniently do if the order of filter's parameters were swapped: filter :: [a] -> (a -> Bool) -> [a] filterOneToTen = filter [1..10] -- ?? But for postfix function application, this latter order is the one you want: [1..10].filter even is a lot more intuitive than even.filter [1..10] So if you have postfix function application in the language, you end up with a zero-sum situation where a function can be convenient to partially apply, or it can be convenient to use with postfix notation, but (unless it's single-argument) it can't be both. You'll end up with some people preferring postfix notation and writing their functions one way, other people preferring partial application and writing their functions the other way, and a lot of frustration when people from one group want to use functions written by the other. I hope you'll agree that writing two versions of every function is not a satisfactory solution. Having postfix application supply the last argument rather than the first one -would- be satisfactory, but in Haskell's case it's hard to tell which one that is. (Thanks to the fact that multi-argument functions are just single-argument functions returning other single-argument functions.) Given this incompatibility, my humble opinion is that we should choose one or the other. All of our existing functions, with only a few irritating exceptions (writeIORef, I'm looking at you), are optimized for partial application, so we should stick with it. To finally get around to the point: All of this said, record.field is still the most readable, intuitive, and familiar syntax for selecting a field from a record that I know of. It would be nice to have it. If we restrict this postfix notation to only selecting fields from records, then the second problem from above is completely obviated, and the first one is at least greatly alleviated, to the point where I think the benefit outweighs the harm. So my preferred solution is: - Selecting fields from records can be written (equivalently) using either prefix or postfix notation; - Everything else can be written only with prefix notation. My second-choice solution is to not introduce postfix notation.

The first problem is that mixing prefix and postfix function application within the same line makes it harder to read. When you read code to try to understand what it does, the direction you like to go in is "here's some object, first do this to it, then do that to it, then do this other thing to it, then this fourth thing to produce the final result". In Haskell code with prefix application, this is easy: you read it from right to left. I've argued before (don't think here - most likely on Programmers.SE)
On 03/02/2012 11:13, Gábor Lehel wrote: that even mathematicians think imperatively, often viewing an expression as if it were a right-to-left series of imperative mutations. I get called an idiot when I say that. But...
This is the smaller problem. If prefix and postfix notations are completely interchangeable, then we can at least expect people to not make their own code hard to read, and to stick to one or the other within an expression. (If they're *not* interchangeable, and one or the other is required in some cases, then it's a bigger problem.) There are already some right-associative operators and some left-associative operators. So the question isn't really about the language grammar, but how something "reads".
But then, even in Haskell, where order matters, most things read from left to right. With the monadic bind, for example, the left argument is "before" the right argument. In let expressions, the first definition is the leftmost definition. In a list or a tuple, the leftmost item is normally considered the first item - by definition it's the head in a list. When currying arguments, the leftmost argument is the first to curry. This isn't an absolute, of course, but still - function composition with the dot is arguably the odd-one out. If the point is that TDNR should use some other symbol, I have some sympathy with that, but Haskells freedom with operator identifiers has a downside - there are few if any completely safe symbols available to use. Unless of course we choose a completely new character that has never been available before... http://www.geek.com/articles/geek-pick/unicode-6-1-released-complete-with-em...

Gábor Lehel
On Fri, Feb 3, 2012 at 10:30 AM, AntC
You seem to be not alone in wanting some special syntax for applying field selectors (see other posts on this thread). H98 field selectors don't do
wrote: this,
they're just functions.
I'm puzzled why you want different syntax for field selectors. Can you give some intuition?
Here's my problems with allowing postfix application using dot for all functions.
Thank you Gábor for explaining this so clearly. I can see that mixing prefix and postfix style would be confusing. I suppose in other programming paradigms (like database access) record.field is regarded as 'atomic', not as function application. And under my proposal (or SORF or TDNR) it's atomic-ish, because the dot binds tighter than **even function application**. We already have in H98 field selection as function application. I'm keen not to break that, because then I can use dot notation on H98-style records. And I'm very keen that field selection (continue to) be equivalent to function application, precisely so that people who prefer prefix notation can "carry on regardless". Do people really write code with huge pile-ups of functions prefix upon prefix? Wouldn't that be confusing even when it's unidirectional? I've seen some examples in other threads mixing dot notation with function composition with user-defined operators built with a dot (like >.< ) and a sprinkling of parentheses. They were indeed unreadable, but frankly, I don't think that was purely down to the dot notation.
The first problem is that mixing prefix and postfix function application within the same line makes it harder to read.
I can see that. As you say, it's hopeless if readers have to start in the middle somewhere and work outwards, swerving to and fro. If binding-dot is just (reverse) function application, I can't stop people exploiting it for more than field selection, and some functions just 'feel' like fields. SPJ gave the examples of: customer.fullName -- fullName is a function to concat first ++ last shape.area -- polymorph area overloded for each shape And then there's: datetime.month -- calculate month from number-of-days format tuple.fst string.last name.middleInitial address.streetNumber polar.theta.arctan We're on the slippery slope! Where will it end? And now that I've found it, I so love: customer.lastName.tail.head.toUpper -- Yay! I notice that for prefix functions you do sometimes need a bit of trickery to deal with partial application and inconvenient order of parameters. Of course there's parentheses to help, but there's also a family of combinators, especially: ($) -- loose-binding function application (.) -- function composition So I'm going to take your post as a challenge: can we build a family of combinators for postfix style? The objective is to 'keep up the momentum' left to right. I've already been using one such: (.$) = flip ($) -- looks combinator-ish to me! (.$!) = flip ($!) -- strict version customer.lastName .$ tail .$ head .$ toUpper -- Yay.$!
The other problem is that, in order to make partial application convenient, you want to put your function's parameters in the order of least specific to most specific. If you want to make postfix application convenient, you have to do the reverse.
True-ish. I guess it depends how 'tight' you feel the function binds with it's least specific parameters. What's atomic?
For example, take the filter function from the Prelude:
filter :: (a -> Bool) -> [a] -> [a]
But for postfix function application, this latter order is the one you want:
[1..10].filter even is a lot more intuitive than even.filter [1..10]
Agreed. Easy. How do you like these?: [1..10] .$ filter even [1..10] .$ filter even .$ sum ^ 2 [1..10] .$ filter even .$ foldr (+) 0 ^ 2 I'm looking at those thinking 'Oh yes! foldr (+) 0 is atomic-ish'.
... You'll end up with some people preferring postfix notation and writing their functions one way, other people preferring partial application and writing their functions the other way, and a lot of frustration when people from one group want to use functions written by the other.
Yeah, like little-endians vs. big-endians.
I hope you'll agree that writing two versions of every function is not a satisfactory solution.
Absolutely! And we've a huge body of code defined in prefix form, we don't want to re-engineer that. And there's a whole body of mathematics/algebra/logic that uses prefix style.
To finally get around to the point:
All of this said, record.field is still the most readable, intuitive, and familiar syntax for selecting a field from a record that I know of. It would be nice to have it.
Indeed!
If we restrict this postfix notation to only selecting fields from records,
Would you like to include 'virtual' fields like fullName or area? Or fst or last or middleInitial?
So my preferred solution is:
- Selecting fields from records can be written (equivalently) using either prefix or postfix notation; - Everything else can be written only with prefix notation.
My second-choice solution is to not introduce postfix notation.
Noted. (And from the above, you won't expect me to agree.) I guess GHC HQ gets the final decision. Glad I'm not having to mediate. Thank you for raising the issue so cogently. AntC

On Fri, Feb 3, 2012 at 2:37 PM, AntC
Do people really write code with huge pile-ups of functions prefix upon prefix? Wouldn't that be confusing even when it's unidirectional?
Not really. Pipeline-like chains where you apply each function to the result of the previous one are quite common and readable, whether in the shell, Haskell, or your 'Yay!!' example. But possibly we aren't referring to the same thing.
I've seen some examples in other threads mixing dot notation with function composition with user-defined operators built with a dot (like >.< ) and a sprinkling of parentheses. They were indeed unreadable, but frankly, I don't think that was purely down to the dot notation.
Well, yeah. If you want to write confusing code you can certainly do that. You can do it already. I don't think adding another way to do it is a huge problem. I think you can expect people to not shoot themselves in the feet intentionally. What -is- a problem is if you are forced or encouraged to write confusing code (because there's no other way to do it or because it's the path of least resistance), which is why I dislike proposals which make postfix application mandatory for some purposes, or which make it have different behaviour from normal prefix application.
And now that I've found it, I so love:
customer.lastName.tail.head.toUpper -- Yay!
I agree that this is nice, but it only works with single-argument functions.
I notice that for prefix functions you do sometimes need a bit of trickery to deal with partial application and inconvenient order of parameters. Of course there's parentheses to help, but there's also a family of combinators, especially: ($) -- loose-binding function application (.) -- function composition
So I'm going to take your post as a challenge: can we build a family of combinators for postfix style? The objective is to 'keep up the momentum' left to right.
I've already been using one such: (.$) = flip ($) -- looks combinator-ish to me! (.$!) = flip ($!) -- strict version
customer.lastName .$ tail .$ head .$ toUpper -- Yay.$!
I don't see a benefit here over plain dot...
For example, take the filter function from the Prelude:
filter :: (a -> Bool) -> [a] -> [a]
But for postfix function application, this latter order is the one you want:
[1..10].filter even is a lot more intuitive than even.filter [1..10]
Agreed. Easy. How do you like these?:
[1..10] .$ filter even [1..10] .$ filter even .$ sum ^ 2 [1..10] .$ filter even .$ foldr (+) 0 ^ 2
I'm looking at those thinking 'Oh yes! foldr (+) 0 is atomic-ish'.
Oh, well, this looks alright. Hmm.
If we restrict this postfix notation to only selecting fields from records,
Would you like to include 'virtual' fields like fullName or area? Or fst or last or middleInitial?
I guess these would be OK. Virtual fields are effectively required to be single-argument, so you don't encounter the argument-order problem, and if you can write them equally prefix and postfix then you can avoid the mix-and-match problem. But this opinion might be obsolete, see below.
So my preferred solution is:
- Selecting fields from records can be written (equivalently) using either prefix or postfix notation; - Everything else can be written only with prefix notation.
My second-choice solution is to not introduce postfix notation.
Noted. (And from the above, you won't expect me to agree.) I guess GHC HQ gets the final decision. Glad I'm not having to mediate.
If postfix code can be conveniently written using your (.$) combinator (and presumably its extended family), with no changes required to existing or future functions, I guess it could all work out. What I'm afraid of is that introducing postfix notation results in a pressure to make functions convenient to use with it, and then we eventually end up in the morass I described. If we can reasonably expect that having the postfix combinators around will remove that pressure or that people will resist it, and that we won't end up with a proliferation of writeIORef-endian functions on Hackage, I guess I would be okay with it. I'm not sure what we would need to be able to reasonably expect that. (Not that me being okay with it is required for anything.)

Gábor Lehel
On Fri, Feb 3, 2012 at 2:37 PM, AntC
wrote:
Do people really write code with huge pile-ups of functions prefix upon prefix? Wouldn't that be confusing even when it's unidirectional?
Not really. Pipeline-like chains where you apply each function to the result of the previous one are quite common and readable, whether in the shell, ..
Thank you for reminding me! Unix Pipelining -- that's where I've seen it. And in the shell, the pipelining is postfix. My (.$) is loose-binding postfix application. But let me do: (.|) = flip ($) -- same as (.$), but suggestive of the pipe customer.lastName -- field select, dot 'allowed' per Gábor .| tail -- function apply, dot not .| head .| toUpper -- are you warming to it? [1..10] .| filter even .| foldr (+) 0 .| (^ 2) -- the parens is a bit of a let-down
What -is- a problem is if you are forced or encouraged to write confusing code (because there's no other way to do it or because it's the path of least resistance), which is why I dislike proposals which make postfix application mandatory for some purposes, or which make it have different behaviour from normal prefix application.
Totally agree, that's one of the things I didn't like about TDNR or SORF. That's why I'm trying to support both prefix and dot-notation field selectors. The main thing, though, I like about field selectors as functions (and nothing more) is that we've then got a mechanism for overloading them to select from multiple record types, and the mechanism is rock-sold instance resolution, not some semi-syntactic/semi-type-driven dodginess. [I'll let you into a secret about my plan for world domination: If field selection is just an (overloaded) function, we can apply it to other things than records. tuple.fst We can turn our data dictionary into a type dictionary: newtype Customer_id = Customer_id Int We can 'hunt out' the customer_id from a tuple: tuple.customer_id (Using instance resolution to the only Customer_id in that tuple.) And now we've got tuples as anonymous records. Crucially: we don't care about the field's position within the tuple. We could have two tuples with the same fields, but different order. And treat them as equivalent at the type level. (What relational theory calls 'union compatible'.) End of mad moment.]
If postfix code can be conveniently written using your (.$) combinator (and presumably its extended family), with no changes required to existing or future functions, I guess it could all work out. What I'm afraid of is that introducing postfix notation results in a pressure to make functions convenient to use with it, and then we eventually end up in the morass I described.
Totally agree, I think order of parameters in declarations should continue to expect prefix style, with least specific first (that is, leftmost).
I'm not sure what we would need to be able to reasonably expect that.
I think time for others 'listening in' to develop the family of combinators!

Quoth AntC
We're on the slippery slope! Where will it end?
And now that I've found it, I so love:
customer.lastName.tail.head.toUpper -- Yay!
... compared to present practice, with where dot is function composition only - (toUpper.head.tail.lastName) customer So two competing meanings of ".", where one is literally the reverse of the other. Of course we won't be able to spell composition without spaces any more, so technically the backwards and forward sense of . are distinct, but it seems kind of unfortunate anyway. ... If you'll consider an idea from the peanut gallery ... for me, the dot notation for fields may as well be "spelling" as an operator - that is, customer.lastName deploys a field named ".lastName". If someone modified Haskell to allow postfix notation from this perspective, when compiler sees "customer.lastName", it would look for an identifier ".lastName", so it would work only where the fields are so declared: data Customer = Customer { .lastName :: String, .firstName :: String } Without explicit dot nomenclature (as per current practice), only normal function application syntax would be supported (as per current practice.) Unspaced composition (fromInteger.ord) would still be broken, I suppose, but the error (Not in scope: `.ord') would at least be pretty obvious. Donn

Donn Cave
Quoth AntC
, ... We're on the slippery slope! Where will it end?
And now that I've found it, I so love:
customer.lastName.tail.head.toUpper -- Yay!
... compared to present practice, with where dot is function composition only -
(toUpper.head.tail.lastName) customer
So two competing meanings of ".", where one is literally the reverse of the other. Of course we won't be able to spell composition without spaces any more, so technically the backwards and forward sense of . are distinct, but it seems kind of unfortunate anyway.
Thanks Donn. I can see we aren't going to agree on this, so I'll be brief. (I'll use my limited time to gather the proposal properly on to a wiki.) It was a surprise to me that dot without spaces around is still legal syntax for function composition. So yes, we're going to break code (and hearts, by the sound of it). I'm proposing my record fields so that selectors are just functions. Then it's independent of dot notation. (It's the semantics I'm far more concerned with.) You (Donn) can then avoid 'switching on' dot as tight-binding reverse func apply, and nothing's got broken. (On the other hand, the change in semantics is so dramatic switching it on would get compile failures in typing expressions, so I don't see any danger of running broken code.) We could use something other than dot for the purpose (# has been suggested), but the trouble is that the user-defined operator space has got used up. I see that as part of introducing tight-binding reverse func apply, I also need a loose-binding version (counterpart to ($) in the Prelude). (.$) seems most natural, but probably that's already extant in user-defined code. So the advantage of dot (aside from it being familiar from other programming paradigms) is that we know the design space isn't used up.
...
If you'll consider an idea from the peanut gallery ... for me, the dot notation for fields may as well be "spelling" as an operator - that is, customer.lastName deploys a field named ".lastName".
No, I no longer think it's just spelling. (I can see my Yay example is pushing the innovation too far too fast.) Examples which might be easier to swallow: customer.fullName shape.area date.dayOfWeek name.middleInitial list.length Are all pseudo- or virtual or calculated 'fields'. (Or if not fields, then attributes or properties.) I presume you're not suggesting we have both a function `area' and a pseudo- field `.area'? Perhaps we could allow some graphic char as a prefix to field names? (perhaps # because it's already allowed as part of magic-hash names? But it would be part of the name, _not_ an operator. customer.#firstName <===> (#firstName customer) AntC

Quoth AntC
It was a surprise to me that dot without spaces around is still legal syntax for function composition.
It isn't even unusual. You can find stuff like "fromIntegral.ord" in packages downloaded to build cabal-install for example. It graphically appeals to the notion of a function composed of several functions, so the programmers in question will likely not even be repentant! It's hard to imagine this all going anywhere, really, without some way around the code breakage. Maybe a different separator, like record\field, that really doesn't occur in infix like that.
Are all pseudo- or virtual or calculated 'fields'. (Or if not fields, then attributes or properties.)
I presume you're not suggesting we have both a function `area' and a pseudo- field `.area'?
Well - there's no conflict between those two names, if `.area' is an identifier that starts with a dot. But virtual or calculated fields would presumably not be supported. Depends on whether it's legal to define a function `.area', or `.' spelling is allowed only for declared record fields. Personally I think the latter would be the right choice there - left of the dot must be a record value, right of the dot must be a field declared for that record. I understand this is not the direction you're going. Donn

Donn Cave
You can find stuff like "fromIntegral.ord" in packages downloaded to build cabal-install for example. It graphically appeals to the notion of a function composed of several functions, so the programmers in question will likely not even be repentant!
Data.Char.toUpper -- a name composed of several names shape.position.xCoord -- a structure composed of several structures Here's an off-the-wall idea for the syntactics: - Where there's a block of names with dot separators (and no spaces). - The dots must be either all postfix apply or all prefix compose. - Postpone analysing until we've got some type info for the sub-names. - The types must interlock either left-to-right or right-to-left. So now we know whether we're prefix or postfix. - Then we can adjust the AST for loose-binding vs tight-binding. (As happens for operator precedence.) ?Do we call this "Type-Directed Syntax Resolution" ;-) (By the way, natural languages do this sort of stuff all the time. In fact they revel in it: "Eighth Army Push Bottles Up German Rear." http://languagelog.ldc.upenn.edu/nll/?p=3708 ) The more I think about it, the more the pseudo-fields makes sense, the more I want field selectors to be just functions. There's an interesting example in Wadler's original paper that became View Patterns "Views: A way for pattern matching to cohabit with data abstraction" [1987], 4. "Viewing a complex number in cartesian and polar coordinates". We may want our implementation of complex to be abstract. We provide (pseudo-) fields to select the coordinates. Then they're ever-so like methods for an (abstract) object. Also we want the (pseudo-) fields to be updatable, which means field update needs to be polymorphic (overloaded). Then all I need is a type-(or kind-) level 'peg' for the name, and an instance for Has/get/set. AntC

Crash blossoms, while amusing, are not a desirable feature of a programming
language. They are specifically a failure to communicate clearly.
On Feb 6, 2012 6:38 PM, "AntC"
Donn Cave
writes: You can find stuff like "fromIntegral.ord" in packages downloaded to build cabal-install for example. It graphically appeals to the notion of a function composed of several functions, so the programmers in question will likely not even be repentant!
Data.Char.toUpper -- a name composed of several names shape.position.xCoord -- a structure composed of several structures
Here's an off-the-wall idea for the syntactics: - Where there's a block of names with dot separators (and no spaces). - The dots must be either all postfix apply or all prefix compose. - Postpone analysing until we've got some type info for the sub-names. - The types must interlock either left-to-right or right-to-left. So now we know whether we're prefix or postfix. - Then we can adjust the AST for loose-binding vs tight-binding. (As happens for operator precedence.)
?Do we call this "Type-Directed Syntax Resolution" ;-)
(By the way, natural languages do this sort of stuff all the time. In fact they revel in it: "Eighth Army Push Bottles Up German Rear." http://languagelog.ldc.upenn.edu/nll/?p=3708 )
The more I think about it, the more the pseudo-fields makes sense, the more I want field selectors to be just functions. There's an interesting example in Wadler's original paper that became View Patterns "Views: A way for pattern matching to cohabit with data abstraction" [1987], 4. "Viewing a complex number in cartesian and polar coordinates".
We may want our implementation of complex to be abstract. We provide (pseudo-) fields to select the coordinates. Then they're ever-so like methods for an (abstract) object.
Also we want the (pseudo-) fields to be updatable, which means field update needs to be polymorphic (overloaded). Then all I need is a type-(or kind-) level 'peg' for the name, and an instance for Has/get/set.
AntC
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I'm proposing my record fields so that selectors are just functions. Then it's independent of dot notation. (It's the semantics I'm far more concerned with.)
Folks, I've put my 'Record in Haskell' proposal on the wiki http://hackage.haskell.org/trac/ghc/wiki/Records as suggestion 5 Declared Overloaded Record Fields. Thanks to the voiciferousness on this thread, dot notation is completely optional. Feedback welcome. AntC -- View this message in context: http://haskell.1045720.n5.nabble.com/Some-thoughts-on-Type-Directed-Name-Res... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Mon, Feb 20, 2012 at 4:41 AM, AntC
Folks, I've put my 'Record in Haskell' proposal on the wiki http://hackage.haskell.org/trac/ghc/wiki/Records as suggestion 5 Declared Overloaded Record Fields.
Thanks to the voiciferousness on this thread, dot notation is completely optional.
Feedback welcome.
Thanks for writing it up, I admit I was having trouble following across the various email threads. Surprisingly, your ideas are very similar to my own. I'm not sure if this is a good thing or a bad sign, but naturally I'm in favor. I was wondering whether it wouldn't make sense to have some syntax within the record itself, instead of at the top level, to declare, "I'm definitely declaring a new record field", versus "I'm definitely re-using an existing record field", versus "If this record field already exists I'm re-using it, otherwise I'm declaring it". (It doesn't necessarily make sense to have all three - the second one might be cumbersome, or the third one might be error-prone - but they seem like the options.) The existing, unadorned record syntax would mean "I'm definitely declaring a new record field", because that's what it already means. Simply leaving off the type annotation to indicate otherwise sadly wouldn't work because, as you mention, that means that it's the same type as the next field. So something like: data Rec1 = Rec1 { field1 :: Int, field2 :: Char } -- declare field1 :: Int and field2 :: Char fields data Rec2 = Rec2 { import field1, field3 :: String } -- reuse field1 :: Int, declare field3 :: String data Rec3 = Rec3 { field3 :: String } -- declare field3 :: String, but error: already declared Hopefully someone can think of better syntax than my "import field1" above. Regarding the polymorphic update / higher-rank fields issues, I'm not competent to address them in earnest, but: isn't this primarily an ImpredicativeTypes issue? If GHC had full support for ImpredicativeTypes (whatever that means), would it work? ~g

Gábor Lehel
On Mon, Feb 20, 2012 at 4:41 AM, AntC
wrote:
Folks, I've put my 'Record in Haskell' proposal on the wiki http://hackage.haskell.org/trac/ghc/wiki/Records as suggestion 5 Declared Overloaded Record Fields.
Feedback welcome.
I was wondering whether it wouldn't make sense to have some syntax within the record itself, instead of at the top level, to declare, "I'm definitely declaring a new record field", versus "I'm definitely re-using an existing record field", versus "If this record field already exists I'm re-using it, otherwise I'm declaring it". ...
We're trying to minimise the changes (and be backward compatible, if possible), so I think a single compiler option at module level is enough, without introducing tricky syntax in the record decls. Option absent means H98 behaviour. Option present means _all_ my record decls are using pre-defined record fields. Note that this only affects the modules where the records (and fieldLabels) are declared. In the application code which uses the records, just apply the field selector function to the record, or use familiar record update syntax. You don't have to know how the record or fields were declared. (That is, you can import H98 style records and DORF style records quite happily.) That suggests the best way to organise the database definitions/decls is: - base module: data dictionary (fieldLabels only) - record/structures module(s) grouped by application areas: records only plus interface to your data store; plus validation and manip utilities - application modules: business code possibly plus ad-hoc records (may be decl'd H98 style) Well stap me if that way of organising isn't best practice anyway!
Regarding the polymorphic update / higher-rank fields issues, I'm not competent to address them in earnest, but: isn't this primarily an ImpredicativeTypes issue? If GHC had full support for ImpredicativeTypes (whatever that means), would it work?
~g
Thanks Gábor, neither am I really competent, which is why I asked SPJ to look at an early prototype. Since he says it's an unscalable hack, I'll stop there. At least my proposal uses Has/get/set (with its type-level sugar) and supports type-changing update. So (I reckon) it's equal to or ahead of any other proposal -- except for those which need whole-scale syntax re-engineering and breaking a whole heap of code. AntC

On 4/02/2012, at 12:13 AM, Gábor Lehel wrote:
All of this said, record.field is still the most readable, intuitive, and familiar syntax for selecting a field from a record that I know of.
Having learned COBOL and Algol 68 before Haskell was dreamed of, I regard field OF record as the most readable, intuitive, and familiar syntax. Given our background in reading natural language text, most of us probably thought once upon a time that '.' was the most readable, intuitive, and familiar syntax for terminating a statement, and in COBOL, NDL, and Smalltalk, it _is_. There's certainly nothing about a dot that suggests field selection, *unless* you happen to be familiar with a programming language that does it that way. If we are going to let compatibility with Pascal or C or the like be our guide to readability and intuition, when are we going to switch from "!" and "!!" for indexing to _[_]?

Richard O'Keefe
On 4/02/2012, at 12:13 AM, Gábor Lehel wrote:
All of this said, record.field is still the most readable, intuitive, and familiar syntax for selecting a field from a record that I know of.
Having learned COBOL and Algol 68 before Haskell was dreamed of, I regard
field OF record
as the most readable, intuitive, and familiar syntax. Given our background in reading natural language text, most of us probably thought once upon a time that '.' was the most readable, intuitive, and familiar syntax for terminating a statement, and in COBOL, NDL, and Smalltalk, it _is_. There's certainly nothing about a dot that suggests field selection, *unless* you happen to be familiar with a programming language that does it that way. ...
Richard, now you're just being playful. Database access languages used record.field since COBOL days (well certainly before SQL in 1969). Assembler and linker languages often allowed dots within names. I presume IPv4 dot-decimal comes from this. I think the use of dot comes from section and sub-section numbering in large documents. I have no idea when that dates from, but off the top of my head: Principia Mathematica, Russell and Whitehead 1910 Tractatus Logico-Philosophicus, Wittgenstein, 1918 (Admittedly Princ Math also uses dot (infix operator) as logical product. As well, there's a dot separator between a quantifier's list of bound variables (upside-down A, backwards E) and the bound term. Church's lambda notation similarly uses a dot to separate the bound variables.) There is one 'odd man out' when it comes to dot notation: A few little-known programming languages have for some reason bucked the well- established convention of small circle for function composition. There's certainly nothing about a dot that suggests function composition, *unless* ... AntC

On 7/02/2012, at 1:41 PM, AntC wrote:
Richard, now you're just being playful.
"Half fun and full earnest." I *do* regard 'field OF record' as far more readable, intuitive, &c than 'record.field'. With the number of meanings '.' already has in Haskell, I *do* regard any attempt to overload it for field access as deeply problematic and likely in practice to push much Haskell code over the readability event horizon. Anyone who has had occasion to write Fortran in the last 20+ years has had to discover just how quickly you can get used to using 'record%field'. I'm not really a COBOL programmer, but Prolog and Erlang and Smalltalk taught me well that '.' in a programming language can perfectly well mean exactly what it means in English: end of statement. I just do not buy the idea that the connection between dot and field access is anything more than a habit of mind engendered by a few languages or that it should be respected any more than the habit of using a(i) -- Fortran, Simula 67, Ada, Dijkstra's notation, PL/I -- or a[i] -- Algol 60, Algol 68, Pascal, C and its horde of delirious imitators -- for array access. The idea of using #field for a field access function has of course an appeal to people familiar with ML or Erlang. The connection with ML is very close. # is already used. I rather like field¶ record ([the] field[part] [of] record), with the ¶ Pilcrow reminding me of Part. Following ML, we could perfectly well allow 3¶ as well, meaning "field 3 of any tuple that _has_ a field 3, the type to be resolved by context".

On 2/7/12 4:52 PM, Richard O'Keefe wrote:
Anyone who has had occasion to write Fortran in the last 20+ years has had to discover just how quickly you can get used to using 'record%field'. I'm not really a COBOL programmer, but Prolog and Erlang and Smalltalk taught me well that '.' in a programming language can perfectly well mean exactly what it means in English: end of statement. I just do not buy the idea that the connection between dot and field access is anything more than a habit of mind engendered by a few languages or that it should be respected any more than the habit of using a(i) -- Fortran, Simula 67, Ada, Dijkstra's notation, PL/I -- or a[i] -- Algol 60, Algol 68, Pascal, C and its horde of delirious imitators -- for array access.
Hear hear! I'd be perfectly fine with %field (alas the Ratio type), or #field (alas -XMagicHash), or @field (alas confusion in Core for type application), or any other number of options--- but the .field choice is far too fraught with issues and the connotations it brings up are not at all convincing to me. It's not like we use angle brackets for passing arguments to type constructors, nor parentheses to pass arguments to functions, nor any of the conventional notations for array access, nor... -- Live well, ~wren

On 06/02/2012 23:58, Richard O'Keefe wrote:
On 4/02/2012, at 12:13 AM, Gábor Lehel wrote:
All of this said, record.field is still the most readable, intuitive, and familiar syntax for selecting a field from a record that I know of. Having learned COBOL and Algol 68 before Haskell was dreamed of, I regard
field OF record COBOL in particular isn't a well-known exemplar of readability. It's widely seen as a bad joke. I have used COBOL myself, and largely agree with that, with the proviso that I used COBOL a long time ago and have repressed most of the details.
If we are going to let compatibility with Pascal or C or the like be our guide to readability and intuition, when are we going to switch from "!" and "!!" for indexing to _[_]? So far as I can see, there are two likely principles behind this choice in Haskell - one weak and one quite strong. One is that we don't have expressions with syntactic forms other than prefix functions and infix binary operators, except for a few built-in constructs (case, let, ...) which aren't functions. There are no special functions with special
Redundancy can be important for readability, but you can have too much of anything, and in COBOL the level of redundancy is most kindly described as "cluttered with excessive verbosity". To be fair, "field OF record" isn't bad in that sense. However, it would defeat the purpose of TDNR - the record isn't first, and therefore cannot be used (given a left-to-right typing direction) as a context to offer member name suggestions. Also, even when I used COBOL (late eightees, early nineties) I'm pretty sure it supported "record.field". I don't remember using it, but then I don't remember using "OF" either - a side effect of loading one record at a time into working storage and effectively having a separate variable for each field. Anyway, assuming I'm not suffering from worse-than-usual memory, COBOL accepted this common convention. On the more general point of choosing an alternative operator, I agree to a point, but familiarity does count for something. Others will point out that Haskell dares to be different, but it's possible to be too daring and too different. Being different for the sake of being different is for those teenagers who go on about being "random" and whatever else they go on about these days. The success of languages like Java, C# and C++ is based on familiarity. I think Haskell should dare to be different when there's a point to that - where necessary based on a principle. We have type classes rather than OOP classes for a principled reason. We have the IO monad rather than effectful functions for a principled reason. If we don't have traditional field-selection for a principled reason, I think that principle is a very weak one. If names can be scoped to modules, to case expressions, to let expressions etc, why not to records? Of course there's a difference, but IMO it's not an important one. parsing. I view this as a weak principle - not important to the paradigm. OOP languages have supported built-in translations from special notations to functions/methods for a long time. It's a familiar and practical approach to, e.g., allowing programmers to define the semantics of indexing on a new container type. There is, however, the issue of overloaded notation and a possible conflict with currying. Python already uses [] for lists (and list comprehensions) as well as for indexing. However, Pythons syntax and semantics differ from Haskells in many ways. In particular, Python doesn't do currying. The difference between currying in a list parameter and indexing a collection would be much less clear in Haskell if it supported [] for indexing, probably damaging readability and possibly (I haven't checked) causing ambiguity that even the compiler couldn't resolve. In this case again, perhaps Haskell is different for a principled reason - choosing to support currying means that either lists or indexing need a different syntax. IIRC, ML also "dares to be different" WRT indexing - maybe because it too supports currying.

On 8/02/2012, at 2:11 AM, Steve Horne wrote:
On 06/02/2012 23:58, Richard O'Keefe wrote:
On 4/02/2012, at 12:13 AM, Gábor Lehel wrote:
All of this said, record.field is still the most readable, intuitive, and familiar syntax for selecting a field from a record that I know of. Having learned COBOL and Algol 68 before Haskell was dreamed of, I regard
field OF record COBOL in particular isn't a well-known exemplar of readability. It's widely seen as a bad joke. I have used COBOL myself, and largely agree with that, with the proviso that I used COBOL a long time ago and have repressed most of the details.
Like Fortran, COBOL has changed a *lot* since 'a long time ago'. And if you did want to be fair, I didn't praise any other aspect of COBOL, only the naturalness and readability of its notation for accessing a field of a record.
To be fair, "field OF record" isn't bad in that sense. However, it would defeat the purpose of TDNR - the record isn't first, and therefore cannot be used (given a left-to-right typing direction) as a context to offer member name suggestions.
Yes, but why SHOULD there be a specific typing direction? ML manages perfectly fine without it. - #1; stdIn:1.1-1.3 Error: unresolved flex record (can't tell what fields there are besides #1) - #1 (true,3); val it = true : bool - #1 (42,"stuff",false); val it = 42 : int If a right-to-left "typing direction" works well for #field record in one language with constrained Hindley-Milner types, why would it not work well for field¶ record in another language with constrained Hindley-Milner types? Why sacrifice readability (field name precedes record) for the sake of, well, for the sake of what exactly escapes me.
Also, even when I used COBOL (late eightees, early nineties) I'm pretty sure it supported "record.field".
That certainly wasn't the case up to COBOL-85. I don't have a copy of COBOL 2002, so I can't speak for that, but COBOL 74 and COBOL 85 are the only candidates for those dates, and they definitely did NOT support record.field. Since '.' is the statement terminator in COBOL, it's intrinsically unlikely. (You did *check* a COBOL syntax summary, easily found on the web, before posting? Which?)
I don't remember using it, but then I don't remember using "OF" either - a side effect of loading one record at a time into working storage and effectively having a separate variable for each field. Anyway, assuming I'm not suffering from worse-than-usual memory, COBOL accepted this common convention.
Yes, you are suffering from worse-than-usual memory, and it was common practice in some shops to use the same field name in multiple records, so that the "CORRESPONDING" language feature would have some point!
On the more general point of choosing an alternative operator, I agree to a point, but familiarity does count for something. Others will point out that Haskell dares to be different, but it's possible to be too daring and too different. Being different for the sake of being different is for those teenagers who go on about being "random" and whatever else they go on about these days. The success of languages like Java, C# and C++ is based on familiarity.
Using pointy brackets for generic parameters and :: for name scope were not familiar when C++ introduced them. And there was prior art in other languages for *both* of those. One common prior practice, relevantly enough, was '.' for name scope.
I think Haskell should dare to be different when there's a point to that - where necessary based on a principle. We have type classes rather than OOP classes for a principled reason. We have the IO monad rather than effectful functions for a principled reason.
And if C++ can break with prior practice for a practical reason, Haskell can break with prior practice for the same reason: not breaking existing code, fitting into the existing language structure as well as practical.
If we don't have traditional field-selection for a principled reason
We don't have it because we don't need it. And we don't need it because traditional field selection serves two roles: *selecting* one field and *updating* one field. It's a poor way to handle the latter use case, because one often needs to update more than one field. It's not _that_ good for the former use case either, if you need to access more than two fields from the same record. In another functional language that I use, I've noticed what seems to me a marked increase in readability by switching _away_ from field selection to pattern matching.
I think that principle is a very weak one. If names can be scoped to modules, to case expressions, to let expressions etc, why not to records? Of course there's a difference, but IMO it's not an important one.
Nobody is arguing against names being scoped to records. The argument is against using dot for it because dot has too many other uses. We have already seen quite enough horribly confusing examples in this thread.

On 8/02/2012, at 2:11 AM, Steve Horne wrote:
To be fair, "field OF record" isn't bad in that sense. However, it would defeat the purpose of TDNR - the record isn't first, and therefore cannot be used (given a left-to-right typing direction) as a context to offer member name suggestions. Yes, but why SHOULD there be a specific typing direction? ML manages perfectly fine without it. For the only reason that any language feature should exist - because it is useful. In any language with a rich library, it is useful to get hints as to which names are available in a particular context. It saves on the need to memorize thousands - sometimes tens or even hundreds of
On 07/02/2012 22:56, Richard O'Keefe wrote: thousands - of context-sensitive names and their spellings, and saves on getting distracted needing to hunt through manuals.
- #1; stdIn:1.1-1.3 Error: unresolved flex record (can't tell what fields there are besides #1) - #1 (true,3); val it = true : bool - #1 (42,"stuff",false); val it = 42 : int
If a right-to-left "typing direction" works well for #field record in one language with constrained Hindley-Milner types, why would it not work well for field¶ record in another language with constrained Hindley-Milner types? Parsers don't need to care much about left-to-right vs. right-to-left. There can be stack size issues in principle, but that hasn't stopped Haskell offering both left-associative and right-associative infix operators. The ordering has significance in certain ways in functional languages WRT e.g. currying, but that isn't really relevant here. In any case, currying is left-to-right anyway - the left-most argument is curried first.
Why sacrifice readability (field name precedes record) for the sake of, well, for the sake of what exactly escapes me. It doesn't sacrifice readability. The left-to-right order has been chosen by most programming languages, and also used in many other contexts, because many people find it very natural to start from the most general and step down to the more specific in a left-to-right
The point here is for intellisense-like features to work effectively in text editors. The context must come to the left for that to work because... 1. Searching for all possible names within a particular context is easier, and generally more likely to be what is needed, than searching for all possible contexts that contain a particular name. 2. It's easier to type the context, then the marker, then select/type the name than it is to type the marker then the context, then cursor back to before the marker, *then* select the name, then cursor back to after the context. direction. For example, <chapter>.<section>.<subsection>, or <foldername>/<foldername>/<filename>. The left-to-right order isn't especially important in general - but for intellisense it is.
Also, even when I used COBOL (late eightees, early nineties) I'm pretty sure it supported "record.field". That certainly wasn't the case up to COBOL-85. I don't have a copy of COBOL 2002, so I can't speak for that, but COBOL 74 and COBOL 85 are the only candidates for those dates, and they definitely did NOT support record.field. Since '.' is the statement terminator in COBOL, it's intrinsically unlikely. (You did *check* a COBOL syntax summary, easily found on the web, before posting? Which?) If I checked, I wouldn't have said "pretty sure" would I? Those words are generally acknowledged as indicating that someone is working from fallible memory.
On the more general point of choosing an alternative operator, I agree to a point, but familiarity does count for something. Others will point out that Haskell dares to be different, but it's possible to be too daring and too different. Being different for the sake of being different is for those teenagers who go on about being "random" and whatever else they go on about these days. The success of languages like Java, C# and C++ is based on familiarity. Using pointy brackets for generic parameters and :: for name scope were not familiar when C++ introduced them. And there was prior art in other languages for *both* of those.
One common prior practice, relevantly enough, was '.' for name scope. Yes, but C++ also dares to be different, and there's a principled reason for having multiple selection operators in C++. There are multiple namespaces involved. For a smart pointer, for example, . and -> access different namespaces. :: accesses a different namespace too - containing
I think Haskell should dare to be different when there's a point to that - where necessary based on a principle. We have type classes rather than OOP classes for a principled reason. We have the IO monad rather than effectful functions for a principled reason. And if C++ can break with prior practice for a practical reason, Haskell can break with prior practice for the same reason: not breaking existing code, fitting into the existing language structure as well as practical. On not breaking existing code, I'm with you. I once got beaten up rather badly for arguing against PEP 238 (changing the semantics of integer
If we don't have traditional field-selection for a principled reason We don't have it because we don't need it. And we don't need it because traditional field selection serves two roles: *selecting* one field and *updating* one field. It's a poor way to handle the latter use case, because one often needs to update more than one field. It's not _that_ good for the former use case either, if you need to access more than two fields from the same record. Actually, traditional field selection only selects the field. The update is handled by an assignment operator - it really doesn't make sense to
In another functional language that I use, I've noticed what seems to me a marked increase in readability by switching _away_ from field selection to pattern matching. Personally, I don't believe in absolutes, especially WRT readability. Pattern matching is good, but using a case expression just to extract a single field from a record is excessive, causing clutter. That's
That said, I did take a look in an old COBOL book. I didn't find either the dot or the "OF". I vaguely remember that the original COBOL textbook I had actually considered the SORT command so intrinsically difficult that it was outside of the scope of the book. For various reasons, I find it difficult to take COBOL seriously at all, though I wish I had kept that original textbook that didn't cover SORT - it was a much better joke than the book I kept. the mostly the same names, but treating them a different way so that arguably you access different things via those names (or perhaps different aspects of the same things). Haskell already has a . for selecting a name through a context - we call that context a module. According to Bertrand Meyer of Eiffel fame, a class is both a module and a type. Therefore, logically, a type can be a module. "Module" can be considered a general term for a container of named items, basically. But I've already raised the point about simply deciding that record types and record values are modules before. division in Python). Although Python seems to have survived, I still believe it was the wrong thing to do. It would be nice to have some lexical disambiguation in this case - I might prefer some other spelling, so long as the context is on the left and the name is on the right. I was going to propose "?", but that's taken already for implicit parameters - which I don't know the first thing about so I can't guess possible conflicts. I even wondered about adapting the field update syntax so that it no longer does updates, giving something like... <value> { <fieldname> } This might even be extended as a shorthand for tuples of fields. Perhaps it's biggest problem are that it's suggestive of [] for array indexing, which of course Haskell doesn't support, and that it's too close the the record-update syntax for an expression that doesn't return a record, and therefore maybe confusing. One question, though, is... does using the dot in itself break existing code? Take my view about record types and values being modules and I'm not convinced it does. Function composition has functions to the left (and right, of course). Neither a record type nor a record value is a function. Provided the dot has a record type or record value to the left and a field name to the right, there shouldn't be any conflict with existing function composition. try to tie those two operators together. Arguably, the field selection doesn't even read the field - it returns a field identifying thingy (possibly not the correct technical term) which will convert (causing the read) later, when it's found to be an rvalue rather than an lvalue. In principle, Haskell *could* try something similar, using first-class values for field-ids that are statically typed for the record and field types. For modelling imperative code in a pure functional way, it would be possible to do something like this in Haskell now for use with the State monad, though the notation wouldn't be so clean. On accessing more than two fields at once, pattern matching isn't going away. On selecting one field for a read, one of the reasons for the proposal is because quite a few people find that defining a function in a global (or whole-module) scope is a poor way to handle field selection - in particular because you can't have the same field name in several types due to the naming conflict. presumably why we already have the existing functions for reading single fields - but as already mentioned, these cause name-conflict and namespace-pollution issues.
I think that principle is a very weak one. If names can be scoped to modules, to case expressions, to let expressions etc, why not to records? Of course there's a difference, but IMO it's not an important one. Nobody is arguing against names being scoped to records. The argument is against using dot for it because dot has too many other uses. We have already seen quite enough horribly confusing examples in this thread.
Ah - so we're possibly in violent agreement, at least on some points. I very much dislike the one-sided dots, for example, irrespective of whether they are dots or spelled some other way. I'd rather see... <type> <op> <name> : expression for field access function <value> <op> <name> : as above, but with the record argument curried in Using "<type> <op> <name>" may seem verbose when we currently have "<name>", but with a new record notation that doesn't provide module-wide field access functions, field names themselves can be made shorter - at the moment, they often need a type-name prefix anyway for readability and namespace collision avoidance, just as a convention instead of using an operator. A new record notation would be needed, with the same semantics as the existing one except not making the existing field access functions available with a module-level scope. However, if one of the goals of TDNR is to avoid field-name conflicts and namespace pollution, this is I think unavoidable whatever approach is taken. The only alternative would be to deprecate the existing field access functions completely, which is I think unrealistic. A weaker deprecation of the existing notation might work - warn if it's used, but allow the warning to be disabled, and don't threaten to ever remove the notation) but the I haven't given a lot of thought to updates. Partly, I suspect that the existing field update notation would support an intellisense-like feature anyway - treat the braces in much the same way as parens for function calls in other languages.

On 8/02/2012, at 14:16, Steve Horne
I haven't given a lot of thought to updates.
I very much fail to see the point of replacing prefix function application with postfix dots, merely for field selection. There are already some imperfect, but adequate, solutions to the problem of global uniqueness of field names. But you now have mentioned what is really bothering me about this discussion: record updates are simply the most painful and least beautiful part of the Haskell syntax. Their verbosity is astonishing compared to the careful tenseness of every other language construct. If we could spend some effort on designing a decent notation for field updates, I think it would be altogether more likely to garner support than fiddling with dots. Regards, Malcolm

On Wed, Feb 8, 2012 at 2:47 PM, Malcolm Wallace
On 8/02/2012, at 14:16, Steve Horne
wrote: I haven't given a lot of thought to updates.
I very much fail to see the point of replacing prefix function application with postfix dots, merely for field selection. There are already some imperfect, but adequate, solutions to the problem of global uniqueness of field names. But you now have mentioned what is really bothering me about this discussion: record updates are simply the most painful and least beautiful part of the Haskell syntax. Their verbosity is astonishing compared to the careful tenseness of every other language construct. If we could spend some effort on designing a decent notation for field updates, I think it would be altogether more likely to garner support than fiddling with dots.
It's already possible, here's what I've been experimenting with, using fclabels: import Data.Label -- | Compose lenses. (#) :: (a :-> b) -> (b :-> c) -> (a :-> c) (#) = flip (.) infixr 9 # -- | Get: @bval = a#b $# record@ ($#) :: (f :-> a) -> f -> a ($#) = get infixr 1 $# -- | Set: @a#b =# 42 record@ (=#) :: (f :-> a) -> a -> f -> f (=#) = set infix 1 =# Before: setTempo :: Y -> Config -> Config setTempo y config = config { Config.deflt = (Config.deflt config) { Config.tempo = y } } After: setTempo :: Config -> Config setTempo y = Config.deflt#Config.tempo =# y I haven't fully integrated this into my project because there are a lot of labels to convert, but it's promising so far. As far as I'm concerned, the thing to get rid of is the noisy module qualification, which was what my suggestion was aimed at. Then we'd have '#deflt . #tempo =# y', which is pretty concise, if full of #s. Of course some way to resolve 'deflt' and 'tempo' without ugly # markers would be nicer, but I think that would have to be typeclass overloading, which would still require explicit imports for all those label names. They'd also be uncontrollably global, which wouldn't let you use them inside the module but not export. So I'm starting to think that in the absence of changes to typeclasses themselves, a typeclass-using solution is never going to be satisfactory. I agree WRT updates, btw. I don't mind the existing record access very much. It's noisy (I prefix record fields too, so it's even worse: Config.default_tempo . Config.config_default), but it composes, so it just means a few more wrapped lines when they don't fit in 80 columns. 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. I hope I can fix it with lenses, but it's a bit of a hassle trying to retrofit them onto something large.

Quoth Evan Laforge
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? For example, in a better world you could write stuff like modifyConfig :: (Config -> a) -> (a -> a) -> Config -> Config modifyConfig fr fv a = a { fr = fv (fr a) } upTempo config = modifyConfig tempo (+ 20) config ... but today you get "`fr' is not a (visible) constructor field name" So you need a modifyConfigTempo, etc. - when even the above is inconveniently specific, as we'd rather have modifyRecord :: RecordType r => (r -> a) -> (a -> a) -> r -> r I'm not saying "modifyRecord (+ 20) tempo config" would be the ideal syntax for everyone who's been dreaming of records improvement, just trying to get at the underlying problem with minimal syntactic distractions. Nested structure doesn't look like a special problem - modifyRecord innerRecord (modifyRecord inInField (+ 20)) outRecord An operator with some infixing doesn't seem to buy a lot - (innerRecord \{} (inInField \{} (+ 20))) outRecord ... but better might be possible without sacrificing composability. Donn

modifyConfig :: (Config -> a) -> (a -> a) -> Config -> Config modifyConfig fr fv a = a { fr = fv (fr a)
I like this Idea. The only problem I see is this: if I'm trying to write code that is very generic and abstract, how does the compiler know if the update
a { fr = 5 }
is targeting a field fr of the record a, or a variable fr, which is in scope and "points to" a first-class field. The difference depends on the record in question, so the code would work differently depending on the context. I would think it would have to be something like
a { :fr = 5 }
or something else syntactically distinct from current record update syntax. With this and a few more conveniences on record syntax, lenses could go away. For example, I'd love to see a "lambda update" syntax. For example instead of:
setName n r = r {name = n}
we'd write
setName n = \{name = n}
I'd also like to see an "Update field by" syntax. Instead of
addMr r = r { name = "Mr. " ++ (name r) }
we'd write
addMr r = r { name => ("Mr. "++) }
or combining the previous 2:
addMr = \{name=>("Mr. "++)}
feels very terse and "Haskelly" to me. Regards, --J Arthur

Donn Cave
Quoth Evan Laforge
, ... 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

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

Donn Cave
-- 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 "x"s 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

Quoth AntC
Donn Cave
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

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.

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 (type/constructor names included) by making the field names visible. On the use of dots - I only have around 100 keys on my keyboard and most or all available symbols from those keys seem to be used. This use of dot still seems to me like just an extension of dot for <modulename>.<name> for accessing names in a module-based namespace. Further, if the left hand item is a type or value expression, there is no ambiguity with dot for function composition - though this is likely a fatal issue for my idea of allowing dots with data constructor names. Still, we make do without within-particular-constructor field selection now, so that's not such a big deal.

On Thu, Feb 9, 2012 at 12:49 PM, Donn Cave
Quoth Evan Laforge
, ... 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?
I think there are two problems, or at least the way I'm thinking about it I'm decomposing it into two parts. One is the lack of first class and composable update, but that is solved satisfactorily by lenses. The second is how to write those composable first class names without getting RSI. So at least the way I'm thinking currently, only the second needs to be solved. Module qualified names work, but are wordy. Importing unqualified leads to clashes. Typeclasses can solve that, but are global so they're kind of "too" unqualified---no export control. So by that logic, we need either export control for typeclasses or some other kind of automatic resolution which is not global, like my #suggestion. Both would be orthogonal and interesting features in their own right, but now that I think of it maybe export control for typeclasses or closed typeclasses might fit in better. I know a lot of people have wanted those though, so maybe there are serious snags.
For example, in a better world you could write stuff like
modifyConfig :: (Config -> a) -> (a -> a) -> Config -> Config modifyConfig fr fv a = a { fr = fv (fr a) }
upTempo config = modifyConfig tempo (+ 20) config
I think lenses already do better than this, since not only are they more concise than the above (once you've resigned yourself to a few TH splices), they aren't restricted to being only record fields. I've done this before: data Event = Event { event_string :: String, ... } -- oops, strings are inefficient, but Event is already used in many places -- most of which enjoy the convenience of Strings and are not in hotspots: data Event = Event { event_text :: Text, ...} event_string = Text.unpack . event_text With lenses you can do this for update as well: event_string = lens (Text.unpack . event_text) (\s e -> e { event_text = Text.pack s }) You can also enforce invariants, etc. It would be a shame to have a nice record update syntax only to be discouraged from using it because it would tie you too tightly to the current shape of the data structure. There would always be a tension and every time I wrote down a new type I'd waste some time thinking: is the record big enough to want to define functions, or can I get away with direct access? Of course it may *get* bigger later so... It's the same tension as direct access vs. accessors in the OO world, I guess.

Quoth Evan Laforge
On Thu, Feb 9, 2012 at 12:49 PM, Donn Cave
wrote: ... For example, in a better world you could write stuff like
modifyConfig :: (Config -> a) -> (a -> a) -> Config -> Config modifyConfig fr fv a = a { fr = fv (fr a) }
upTempo config = modifyConfig tempo (+ 20) config
I think lenses already do better than this, since not only are they more concise than the above (once you've resigned yourself to a few TH splices), they aren't restricted to being only record fields.
How more concise? Because =# is more concise than `modifyRecord', etc., or is there some real economy of expression I missed out on? Asking because, honestly I didn't get your earlier example - setTempo :: Config -> Config setTempo y = Config.deflt#Config.tempo =# y ... something's missing, I thought - but maybe it's conciser than I can reckon with! The rest - the functions that look like fields, the enforcing invariants, etc. - are cool as lens features, but for Haskell records in general it seems like something that would call for a lot of discussion. Compared to first class record update, where it's easy to see how close to broken the current situation is. Donn

On Thu, Feb 9, 2012 at 10:03 PM, Donn Cave
Quoth Evan Laforge
, On Thu, Feb 9, 2012 at 12:49 PM, Donn Cave
wrote: ... For example, in a better world you could write stuff like
modifyConfig :: (Config -> a) -> (a -> a) -> Config -> Config modifyConfig fr fv a = a { fr = fv (fr a) }
upTempo config = modifyConfig tempo (+ 20) config
I think lenses already do better than this, since not only are they more concise than the above (once you've resigned yourself to a few TH splices), they aren't restricted to being only record fields.
How more concise? Because =# is more concise than `modifyRecord', etc., or is there some real economy of expression I missed out on? Asking because, honestly I didn't get your earlier example -
More concise because in your example (which is also what most of my code looks like), you define a modifyX function and then apply it to form the setField function. To be complete you would have to define a modifyX for every branch in the nested records. It's rare for records go above 3 levels deep, but you can still wind up with quite a function boilerplate style modifyX functions. In the case of lenses, all the relevant modifyX functions are generated automatically and can be composed.
setTempo :: Config -> Config setTempo y = Config.deflt#Config.tempo =# y
... something's missing, I thought - but maybe it's conciser than I can reckon with!
Getting rid of the special operators and eta reduction might make it clearer: setTempo y config = set (Config.tempo `composeLens` Config.deflt) y config
The rest - the functions that look like fields, the enforcing invariants, etc. - are cool as lens features, but for Haskell records in general it seems like something that would call for a lot of discussion. Compared to first class record update, where it's easy to see how close to broken the current situation is.
Well, that's why I'm saying we don't have to build the lens features into the language, though I think at some point one of those lens libraries should make it into the platform and be encouraged as the standard way. I think the field access / modification problem has already been solved, and I can't even think of a better way to do it. You could build them into the language by having the record declaration syntax automatically create lenses instead of plain access functions. But that would make it harder to swap out the implementation, and I don't know if there's sufficient confidence in the implementations that people are ready to commit to one and build it into the compiler. It depends how much people hate the TH gunk implied by not having the derivation built in. I think a reasonable course is to use the TH gunk for now and if the world coalesces on one implementation or if everyone loves the new records and wants to enshrine them in haskell' then it gets built in. TH is good as a trying ground for new features. The thing I think *is* "broken" (well, just awkward, really), is that I have to type 'set (Config.tempo . Config.deflt)' instead of 'set (tempo.deflt)'. Once we get there, then (back to my wacky operators) 'deflt#tempo =# 42 config' is just a jumbled version of the imperative 'config.tempo := 42' only better because it can be partially applied. Then we just add a lens for Data.Map and imperative 'state[block].config.tempo := 42' can be written 'Map.lens block # config # tempo #= 42 config'... not bad! To be sure the only difference with the current situation is that you have to qualify those names.

On Fri, Feb 10, 2012 at 5:31 AM, Evan Laforge
You can also enforce invariants, etc. It would be a shame to have a nice record update syntax only to be discouraged from using it because it would tie you too tightly to the current shape of the data structure. There would always be a tension and every time I wrote down a new type I'd waste some time thinking: is the record big enough to want to define functions, or can I get away with direct access? Of course it may *get* bigger later so...
It's the same tension as direct access vs. accessors in the OO world, I guess.
I thought of this analogy also, but in the context of views/view patterns. They seem to fill a 2x2 grid (not going to try ascii art): accessor functions: map subcomponent of structure, read-only lenses: map subcomponent of structure, read-write view patterns: map whole structure, read-only views: map whole structure, read-write Any of these facilitate separation of interface and implementation: with functions and lenses you define a collection of them representing the logical subcomponents to serve as the interface, whereas with view patterns and views you define an entire new data structure to serve as the interface. (Views feel like they would be more powerful and flexible on this basis, but I haven't thought about it deeply. Perhaps at the price of being less efficient?) The subcomponent vs. whole structure disctinction might be a little bit superficial: there's nothing stopping you from defining a whole-structure lens. I think the difference between that and views is merely convenience of use, but I'm not completely sure. Unfortunately the page where I read a proposal about Views seems to have fallen off the internet and I only partly remember it, so I can't check if this is on the right track. I think it was the one linked from here: http://hackage.haskell.org/trac/haskell-prime/wiki/Views

Although it's a bit off topic, I must say I agree with Malcolm on that. Record-fields-selection-as-functions might be sometime unconvenient, but it is simple and easy to reason about and deal with, with usual Haskell strategies (prefixed names, modules, qualified imports ... business as usual). However, records updating is often painful. A lot of thoughts have been put in lenses, and they quiet improve the state of things. But, franckly, having to pragma template haskell, then prefix all the fields with an underscore, then call a TH splice straight in my code in not a pleasure. Nor is a pleasure to hand-craft lenses. An improvement on this front is probably easier to achieve, would make syntax more consistent, and be immediatly applicable at large scale. Malcolm> I very much fail to see the point of replacing prefix function Malcolm> application with postfix dots, merely for field selection. Malcolm> There are already some imperfect, but adequate, solutions to Malcolm> the problem of global uniqueness of field names. But you now Malcolm> have mentioned what is really bothering me about this Malcolm> discussion: record updates are simply the most painful and Malcolm> least beautiful part of the Haskell syntax. Their verbosity is Malcolm> astonishing compared to the careful tenseness of every other Malcolm> language construct. If we could spend some effort on designing Malcolm> a decent notation for field updates, I think it would be Malcolm> altogether more likely to garner support than fiddling with Malcolm> dots. -- Paul

On 9/02/2012, at 3:16 AM, Steve Horne wrote:
On 07/02/2012 22:56, Richard O'Keefe wrote:
On 8/02/2012, at 2:11 AM, Steve Horne wrote:
To be fair, "field OF record" isn't bad in that sense. However, it would defeat the purpose of TDNR - the record isn't first, and therefore cannot be used (given a left-to-right typing direction) as a context to offer member name suggestions.
Yes, but why SHOULD there be a specific typing direction? ML manages perfectly fine without it.
For the only reason that any language feature should exist - because it is useful. In any language with a rich library, it is useful to get hints as to which names are available in a particular context. It saves on the need to memorize thousands - sometimes tens or even hundreds of thousands - of context-sensitive names and their spellings, and saves on getting distracted needing to hunt through manuals.
You have totally confused me. All of those are good things. NONE of them depends on whether it is field¶record (read "field OF record") or record.field (read "record, oops, I only want part of it".) I think people are losing sight of the fact that code gets read more often than it gets written (at least, if it is code that is _worth_ writing). If the complaint is that certain IDEs designed originally for Java find it easier to give you a hint after "record.", then I would point out that - there is no reason IDEs they cannot be redesigned. Type an expression, then select it if it's complex or don't bother if it's just an identifier, literal, or bracketed, then hit your choice of key (maybe Option-r, ® Reminds me of Record), pick your field from a menu, and the IDE drops field¶ in front of the selected expression and extends the selection to incorporate the field. There is no law of God, Nature, or Man that says the order in which you press the keys has to correspond to the order in which you read things. - languages like C++ and Ada and Java already have the problem that you can write f (x) where the sensible candidates for f depend on what x is. That is, we ALREADY have a need for right context to resolve a left side identifier. Hmm; I was thinking of overloading, but actually, Haskell and C have this problem too. For int x I want close(x) but for FILE* x I want fclose(x). You could write in a C IDE (x, y, z)<magic key> (hey, it could be © for Call) and have a menu of visible functions with that parameter profile pop up. - if you have thousands of context-sensitive identifiers visible in one module, you *desperately* need a better naming convention and shorter import lists. - I have Pharo open on my screen. There are some 3077 classes in it. It insists on popping up these so-called "helpful" menus of names that match what I've typed so far. I find them distracting, and they tend to obscure what I am doing. I *wish* they didn't do that. But I have to admit that I've never actually seen a long list. There are 30,674 'function names' around (both of the numbers are before any of my code is loaded). Again, I start typing something that could be a function name, and up pops a list of candidates. FEH! Despite Smalltalk's lack of any kind of compile-time type checking (this is Pharo, not Strongtalk), again, I've never seen a long list. So I don't see any reason to warp what people *read* away from readability (function before argument) in order to pander to the imagined limitations of writing tools. - if you have thousands of context-sen
The point here is for intellisense-like features to work effectively in text editors. The context must come to the left for that to work because...
And that is the claim I just demolished. The order in which things are entered and the order in which they are display does not have to be the same. That is, after all, one thing that "wizards" do for you.
That said, I did take a look in an old COBOL book. I didn't find either the dot or the "OF".
That is extremely odd, because while COBOL accepts both "field OF record" and "field IN record", people mostly use "OF". That must have been the world's worst COBOL book. (Not unlike the Prolog textbook I met in a university book shop back when Prolog was new: every single example was syntactically illegal.)
Haskell already has a . for selecting a name through a context - we call that context a module. According to Bertrand Meyer of Eiffel fame, a class is both a module and a type.
The Haskell, Ada, Lisp, and CAML designers disagree.
It would be nice to have some lexical disambiguation in this case - I might prefer some other spelling, so long as the context is on the left and the name is on the right. I was going to propose "?", but that's taken already for implicit parameters - which I don't know the first thing about so I can't guess possible conflicts.
It is by now difficult to find an operating system or editor that doesn't support Unicode. A quick review of ISO 8859-{1..12,13..16} -- -12 doesn't exist -- shows that the section character § is common to all of them except -6 (Arabic, but not Persian or Urdu) and -12 (Thai). How about § then? Surely at this late date we can allow ourselves *one* non-ASCII character? The very name of it (*section* sign) suggests taking a part; and if you are totally in love with dot, think of it as a dot with ponytails.
Personally, I don't believe in absolutes, especially WRT readability. Pattern matching is good, but using a case expression just to extract a single field from a record is excessive, causing clutter. That's presumably why we already have the existing functions for reading single fields - but as already mentioned, these cause name-conflict and namespace-pollution issues.
I said pattern matching; I did not say case expressions! What I was talking about was turning f x y = ... x.a ... x.b .... x.a ... x.c ... into f x={a=ping,b=pong,c=pung} y = ... ping ... pong ... ping ... pung ... The increase in readability came in part from the shorter function body but mostly from knowing up front *which* fields were *going* to be relevant in the body.

How about § then? Surely at this late date we can allow ourselves *one* non-ASCII character? The very name of it (*section* sign) suggests taking a part; and if you are totally in love with dot, think of it as a dot with ponytails.
I suggest record的field, or record之field for the more classically minded. And why not some synonyms like recordのfield and recordकाfield, to be inclusive. Once these floodgates are opened we'll never want for operator names again :)

On 9/02/2012, at 1:26 PM, Evan Laforge wrote:
How about § then? Surely at this late date we can allow ourselves *one* non-ASCII character? The very name of it (*section* sign) suggests taking a part; and if you are totally in love with dot, think of it as a dot with ponytails.
I suggest record的field, or record之field for the more classically minded. And why not some synonyms like recordのfield and recordकाfield, to be inclusive.
I chose the most available non-ASCII character I could find. Set the criterion to be "present in most ISO 8-bit character sets" and there are really only two candidates, section sign and degrees sign. That hardly opens flood-gates. It should certainly be limited to characters that do not occur in a word, ruling out record մաս field.

I haven't read the underlying proposals, so I apologize if the following is covered, but my understanding of the discussion is that the x.f notation is intended to disambiguate f to be a field name of the type of x and therefore be advantageous over "f x" notation where f is presently in the global namespace.
Here's another idea, I'm not sure if this one has come up before: f.x desugars as M.f x, where 'M' is the module that defines the type of 'x'. It's an error if 'x' is not monomorphic. You still can't have the same record name in two different records in the same module, but this way the record selector is monomorphic, and it's up to desugaring to find the defining module and if it's imported (I'd expect an error if not). However, I'd still want the prefix functional notation so it could be composed with other functions, and at that point, why have the postfix dot notation at all? Just say that '#x' requires a monomorphic argument, and desugars to 'M.x' where 'M' is the module that the type of its argument lives in, and combine as normal: (#y . #x) record. This way it's not even specific to records.

On 1/02/2012, at 7:10 PM, Anthony Clayden wrote:
On 1/02/2012, at 11:38 AM, AntC wrote:
As soon as you decide to make 'virtual record selectors' just ordinary functions (so they select but not update) , then you can see that field names are also just ordinary functions (for selection purposes). So the semantics for field 'selection' (whether or not you use dot notation) is just function application. So Type-Directed Name resolution is just instance resolution. So it all gets much easier.
Richard O'Keefe wrote: ... Making f x and x.f the same is pretty appealing, but it is imaginable that the former might require importing the name of f from a module and the latter might not. That is to say, it lets f and .f have completely different meanings. Oh the joy! Oh the improved readability! -- on some other planet, maybe.
Hi Richard, I'm not sure I understand what you're saying.
I'm saying that if dot is to do anything at all that it does not do now, then f x and x.f being identical is sort of OK ( though it does rather clash with f . g), but any differences between them would be confusing.
This is all so weird I'm inclined to say that one-sided dot is probably a syntax error, and reject it.
It wasn't a syntax error, it just wasn't intended to be Haskell code at all, just an ad hoc English text abbreviation for "f occurring after a dot". Of course (x.) = \f -> f x and (.f) = \x -> f x are precisely the kind of sections people will expect to be legitimate once they've seen (x.f)... Of course, if f x and x.f mean the same thing, we don't need x.f, do we?
participants (14)
-
AntC
-
Anthony Clayden
-
David Thomas
-
Donn Cave
-
Evan Laforge
-
Gábor Lehel
-
Jonathan Geddes
-
Kevin Quick
-
Malcolm Wallace
-
Paul R
-
quick@sparq.org
-
Richard O'Keefe
-
Steve Horne
-
wren ng thornton