Re: Records in Haskell

Certainly not no conflicts: lambda expressions.
On 30/12/2011, Colin Adams
On 30 December 2011 15:55, Matthew Farkas-Dyck
wrote: On 30/12/2011, Andriy Polischuk
wrote: Yet another idea: Consider using '\' as record access operator. No conflicts with anything at all, and, moreover, it really looks like hierarchical access. Reminds of filesystems though.
I hope this is a joke.
Why?

You're right, i should have written "ambiguities" instead. That was not joke, just i somehow didn't notice Chris Smith answer. However, I think, there are some drawbacks in using dot for that in comparison with qualified imports access. The latter is easier to distinguish from composition by eye, because module-identifier is always one word, starting from uppercase letter (which, moreover, in many editors is highlighted differently). But in field access left operand is not always atomic - it can be expression. Consider this example: quux (y . (foo >.< bar).baz (f . g)) moo It's not that easy to distinguish from quux (y . (foo >.< bar) . baz (f . g)) moo Matthew Farkas-Dyck wrote
Certainly not no conflicts: lambda expressions.
-- View this message in context: http://haskell.1045720.n5.nabble.com/Records-in-Haskell-tp4806095p5111428.ht... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.

On 30/12/2011, Andriy Polischuk
You're right, i should have written "ambiguities" instead. That was not joke, just i somehow didn't notice Chris Smith answer.
Hm. I though at first that if backslash were the selection operator, then there must be programs of unclear semantics, but actually I can't find any. I'm sorry if my earlier message seemed unkind, by the way; it wasn't meant to be.
However, I think, there are some drawbacks in using dot for that in comparison with qualified imports access. The latter is easier to distinguish from composition by eye, because module-identifier is always one word, starting from uppercase letter (which, moreover, in many editors is highlighted differently). But in field access left operand is not always atomic - it can be expression.
Consider this example: quux (y . (foo >.< bar).baz (f . g)) moo It's not that easy to distinguish from quux (y . (foo >.< bar) . baz (f . g)) moo
Yeah, that's why I dislike dot as compose operator (^_~)
Matthew Farkas-Dyck wrote
Certainly not no conflicts: lambda expressions.
-- View this message in context: http://haskell.1045720.n5.nabble.com/Records-in-Haskell-tp4806095p5111428.ht... Sent from the Haskell - Glasgow-haskell-users mailing list archive at Nabble.com.
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Backslash is a possibility then, it seems, but in my opinion breaks the principle of least surprise, i.e. "I can't believe it's not lambda!" Cheers, Matthew Farkas-Dyck

On 12/30/11 10:58 PM, Matthew Farkas-Dyck wrote:
On 30/12/2011, Andriy Polischuk
wrote: Consider this example: quux (y . (foo>.< bar).baz (f . g)) moo It's not that easy to distinguish from quux (y . (foo>.< bar) . baz (f . g)) moo
Yeah, that's why I dislike dot as compose operator (^_~)
Me too. Though I've been told repeatedly that we're in the losing camp :( Given that we want to apply selectors to entire expressions, it seems more sensible to consider the selector syntax to be a prefix onto the selector name. Thus, the selector would be named ".baz" (or ":baz", "#baz", "@baz",...), and conversely any name beginning with the special character would be known to be a selector. Therefore, a space preceding the special character would be optional, while spaces following the special character are forbidden. This has a nice analogy to the use of ":" as a capital letter for symbolic names: function names beginning with the special character for record selectors just indicate that they are postfix functions with some mechanism to handle overloading (whether that be TDNR or whathaveyou). -- Live well, ~wren

Thank you for all your feedback! I updated the wiki page accordingly.
Let us stop and take note of what this feedback is about: the most
convenient syntax for manipulating records, and much of this feedback
applies to any records proposal. That is, there are no fundamental
objections to the implementation of this records implementation. If you
give this kind of general feedback then I assume you are fine with the
name-spacing records implementation.
At this point I feel we are largely waiting on feedback from implementers
to give the implementation critiques or a green light.
But that does not need to stop us from continuing our discussion of the
best syntax for using records.
For the left-right, right-left issue, I added a discussion and potential
solution through partial application:
Partial application provides a potential solution:
(b . .a) r
So if we have a function f r = b r.a then one can write it points-free:
b . .a
Our longer example from above:
e . d . .c . .b . .a
At first glance it may look odd, but it is starting to grow on me. Let us
consider more realistic usage with longer names:
echo . delta . .charlie . .beta . .alpha
Is there are more convenient syntax for this? b <.a
Note that a move to a different operator for function composition
(discussed in dot operator section) would make things easier to parse:
b <~ .a
where the unicode dot might be even nicer.
On Mon, Jan 9, 2012 at 3:15 AM, wren ng thornton
quux (y . (foo>.< bar).baz (f . g)) moo It's not that easy to distinguish from quux (y . (foo>.< bar) . baz (f . g)) moo

You mean this wiki page, right?: http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
That is, there are no fundamental objections to the implementation of this records implementation.
I think that might be overly optimistic... I think there's a risk that SPJ finds an irritating complication to type inference & the rest of us aren't type-system-savvy enough to continue trying to guess at that :) But I think you're referring to whether we object to ad-hoc overloading of record field names (neither parametric nor class-based polymorphism), if no difficulties crop up. Some of the concerns on http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply -- I'm not sure to what extent, but address those concerns rather than require those people to repeat themselves again! :) (If we dodge all those obstacles, well, a better record system is better!) Regardless, I think the proposal needs more precision, so I tried for syntax. And got this thousand word email just about syntax, in several sections of reasoning, sorry! --so here are my conclusions/suggestions up front in case you prefer, most complicated first - look later for details in a different order, referenced by [number]. Given that type inference for expr.field decides between several different possible meanings of "field", which "field"s in scope count as possibilities? I concluded "All identifiers 'field' in top-level scope (i.e. declared in this module or imported unqualified from another module), but no local let/lambda bindings." [1] I have an unrelated record/module system tweak suggestion to prevent leaks of the field-ness of exports meant only as functions. [2] ".field", for any identifier "field", is a postfix operator that binds more tightly than function application. [1] I don't care whether the expression and ".field" are permitted to be separated by whitespace or not. [4] "(.field)" as a section: should it always require parentheses? (assuming there is a way to type-inference the unapplied dot operator usefully at all). [3] The Type.{...} / expr.{...} variations look probably fine ("Syntax for updates" in the wiki). [5] Allow "TyCon.field" for selecting a specific version of "field", but only if there isn't a module in scope as "TyCon" in which case it's interpreted as "Module.field". [7] Allow "expr.TyCon.field" / "expr.Module.field" wherever "expr.field" is allowed. [8] I bikesheddily suggest "field@expr" rather than "expr.field" (I'd be alright with either/both). [6] ===== Defining the basic dot syntax for record field selection ===== [1] .x, for any identifier x, is a postfix operator that binds more tightly than function application. This operator does not constrain the type of its operand or its result. After regular type inference, the type system collects in-scope "x"s and does something to try to choose one. (As a non-type-system-expert, I'm not addressing what "does something" means in this email, besides capitalizing TYPE INFERENCE where I suspect there might (or might not) be extra problems. Anyway, I wish the algorithm do the right thing for "expr.x.y.z".) But which in-scope "x"es does it collect? Regular Haskell scope would completely break "let x = var.x" if we wished to allow "let x = var.x". How about: all record fields 'x' declared in this module or imported (qualified[??] or unqualified) from another module. [[[ Should qualified ones be allowed? Pro: if you import Data.Map qualified, as is common (let's just pretend that Maps have members), then someMap.field works. Pro: it's like allowing qualified imports for instance declaration class-member-definitions. Con: it's not really like that. It makes qualified imports a weaker protection, as the class/instance exception can lead to no ambiguity, but this can lead to ambiguity. The PVP would make a sad face. Con: using unqualified import with (..) would easily bring the field names into scope. Fictitiously, "import qualified Data.Map as Map; import Data.Map(Map(..))". Observation: allowing qualified imports, but not following the class/instance system's style of including everything in the transitive closure of imported modules, still prevents you (Pro) from breaking intentional abstraction barriers, but (Con?) requires you to import the operators for types you receive but don't import. Opinion: only unqualified imports should be part of the selection process. ]]] [[[ Problem: Restricting the selection to only record fields further compromises an existing imperfect property of Haskell: module Library (Type, constructor, deconstructor) where data Type = Constructor { deconstructor :: Int } -- let's pretend it's a bounds-limited int or such. constructor int | int >= 3 && int < 17 = Constructor int Currently, importers of the module can observe that 'deconstructor' is a record-field by importing Library(Type(..)) and getting 'deconstructor' (see [2]--can we change that.). This makes it slightly harder for the library implementer to change that name to a non-record-field. In the proposal, the users might also have gotten used to "expr.deconstructor", and there would be no way to replace that syntax. Possible fix: also require all the type's data-constructors to be in scope. I think that's too big a hammer though. We could punt. We could change the selection to "all top-level names 'x' declared in this module or imported unqualified from another module." Opinion: "all top-level names 'x' declared in this module or imported unqualified from another module." is better and not worse than restricting it to record-fields (provided that it does not burden the type inferencer complexity). Problem: Given that, it's annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. Possible solution: allow "let .deconstruct = \x -> x - 100", possibly with sugary variations. Possibly require a type-signature. Possibility: also allow ".deconstruct = " at top level. (If the dot notation does funny things with TYPE INFERENCE, this might be a dubious idea.) Possible solution: consider *both* local bindings *and* the top-level names that they would normally shadow. (That sounds rather odd; it might work since most of the local bindings with those names will be non-functions and thus not eligible; is it worth it?) Opinion: Just let it be annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. (You can't declare data or classes in let bindings either. Any of these can be improved but I don't think we need to just to have a record system.) [2] We could make this leak fixable thus: "module Library (Type, deconstructor)" does not make "import Library(Type(..))" import "deconstructor" but "module Library (Type(deconstructor))" or "module Library (Type(..))" do make "import Library(Type(..))" import "deconstructor" (and make "import Library(Type(deconstructor))" valid). The difference could even extend to not making "deconstructor" usable in any record syntax (construction, pattern matching, and record update) unless it's imported from somewhere that it's exported syntactically under its type. This might make existing code break. Does anyone think this change might be a good idea? ]]] Suggestion: select all identifiers 'x' in top-level scope (i.e. declared in this module or imported unqualified from another module). ===== Miscellaneous dot-syntax observations ===== [3] Observation: The point-free thought "b . .a" would be exactly the same as the "b . a" we have now with record fields -- except that it behaves a bit differently regarding scope/TYPE INFERENCE. It implies that (.a) is a section of the unary postfix record-field-selection operator (similar to (1 +) being an operator section). "b . .a" also suggests not requiring parentheses for that section when parsing precedence would not require it... for example, parsing precedence would require it in "map (.a) list" if "map .a list" meant "(map.a) list". [4] Should "identifier .field" be disallowed because it's almost certainly a mistake? But " (some long expression here) .field " probably isn't a mistake, so, shrugs. I think it would be equally plausible to require the non-section version of dot to have no spaces on either side, or only require no-space on the right hand side of the dot. [5] The "Syntax for updates" from Frege in the wiki looks fine and syntactically unambiguous to me ("identifier.{" without spaces) - I'd want to think about it later but it seems unlikely to me to go terribly wrong. When you say "If a::T then a.{x=} and a.{x=42} are valid", okay they're valid but as what? as "T.{x=} a" and "T.{x=42} a", or without the "a" argument? e.g. say "If a::T then a.{x=} and a.{x=42} are equivalent to (T.{x=} a) and (T.{x=42} a)". Does TYPE INFERENCE have any more trouble with those than with regular field selection (I don't know)? [6] If we want to bikeshed about what the operator should be ("." or other) : As http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio... says about using dot, "It's standard practice, and that counts for a lot." But if we want to bikeshed and look for an operator that orders things the same way as function application and composition... record.field vs field@record . "@" is already reserved. It could bind more tightly than function application and type-inference differently. Because it's reserved, it doesn't need to require no-spaces-around-it. Here's example from that TDNR page: typical OO: "x.f(3).g(v,w).h" how it would have to be in Haskell+TDNR-dot-syntax: "((x.f 3).g v w).h" or with @ instead of .: "h@(g@(f@x 3) v w)" Which is IMHO only minorly better... but then again, the Frege-ish record proposal might only be doing TDNR for records specifically. (more syntax and semantic discussion at http://www.haskell.org/haskellwiki/TypeDirectedNameResolution ). ...I kind of like @, but think it's a bikeshed: I claim that, if we work out the semantics (big "if"!), that not enough of us are going to say "it's better to have no records than dot-syntax records" [ditto for every other syntax] that the best decision would be "no records!". If this becomes a popular bikeshed, we might just try straw-polling and picking what's popular (rather than get distracted and waste a year -- a common discussion outcome!). (Though, feelings might be stronger than most bikesheds, for such a core language + syntax change...hmm.) ===== Module-related stuff ===== It would be permitted to declare two records in the same scope with the same record field name. GHC would not warn if you shadow record field names with lambda/let-bound variables (It currently does, quite reasonably, warn, iff you enabled -fwarn-name-shadowing && not -XNamedFieldPuns.) This, along with all the other changes, would be contingent on a new flag like -XNamedFieldDots. [7] We would add a syntax "TyCon.name". Thorough option for TyCon.name: (1) If there is a module in scope as TyCon containing a type TyCon with a field "name", it would choose that field. (2) Else if there is a module import in scope as TyCon containing an unqualified, unambiguous* identifier "name", it would choose that. *["unambiguous" meaning it doesn't have two different records with exported fields named "name".] (3) Else if there is a type-constructor in scope TyCon with a named-field "name", it would choose that. (4) Else it would be an error. I think rule (1) can be deleted without changing anything. People usually use module names with dots in them, and type-constructors cannot have dots in them. If a single module decides to import one module "as" the exact name of a type imported from an entirely different module, and the two happen to have some of the same identifiers, perhaps it's okay for silliness to ensue. In fact, given the unlikeliness of inconsistent overlaps like that, I suspect that: Simple option: (1) if there's a module in scope of that name, it means module scope even if that means the lookup fails (2) if there's not a module, see if it can be a type name is equally fine and better because it's simpler. IMHO we shouldn't put these two rules in the other order because it has the ability to break existing code only for the benefit of something that hardly matters either way at all. None of these changes can break existing code. The only breaking change that "-XNamedFieldDots" would introduce is a different meaning of a dot followed without spaces by a lowercase letter. [8] I suggest we should allow expr.TyCon.field (and expr.Module.field I guess) for field-selection too. It's irritating when a syntax can't be qualified without rearranging things (to e.g. "(TyCon.field expr)" or e.g. "(expr::TyCon Int).field" [for single-parameter TyCons like Maybe]). There is no specific interaction with type-classes because Haskell type-classes do not behave like Frege type-classes (as best I can tell from this discussion).

On Mon, Jan 9, 2012 at 2:22 PM, Isaac Dupree wrote: You mean this wiki page, right?:
http://hackage.haskell.org/**trac/ghc/wiki/Records/**NameSpacinghttp://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing That is, there are no fundamental objections to the implementation of this records implementation. I think that might be overly optimistic... I think there's a risk that SPJ
finds an irritating complication to type inference & the rest of us aren't
type-system-savvy enough to continue trying to guess at that :) But I think
you're referring to whether we object to ad-hoc overloading of record field
names (neither parametric nor class-based polymorphism), if no difficulties
crop up. Some of the concerns on http://www.haskell.org/**haskellwiki/**
TypeDirectedNameResolutionhttp://www.haskell.org/haskellwiki/TypeDirectedNameResolutionapply -- I'm not sure to what extent, but address those concerns rather
than require those people to repeat themselves again! :) (If we dodge all those obstacles, well, a better record system is better!) This shouldn't complicate type inference (other than the fact that we must
avoid a left-right bias?) because the record field names are not overloaded
- instead it puts some burden back on the user to add more type
annotations. The difficult aspect of TDNR was that it was assuming
overloading - although there is really no reason why it can't instead
assume name-spacing. TDNR and this record proposal share many of the same
syntax issues you list. Thanks for the detailed feedback! I am travelling
right now, will review when I get a chance.
Greg Weber

Some of your comments seem to not fully recognize the name-spacing (plus
simple type resolution) aspect of this proposal that I probably didn't
explain well enough. Or maybe I don't understand your comments.
For record.field, field is under the record's namespace. A namespace (from
a module or under the new system a record), cannot export conflicting
names, and there this system prevents the importer from every having a
conflict with a record field name because the field is still under the
record's namespace when imported. The type system must resolve the type of
the record, and generally the field cannot contribute to this effort.
Otherwise the comments have some good ideas and details that I will have
time to look over in more detail and incorporate into the wiki later.
On Mon, Jan 9, 2012 at 6:07 PM, Greg Weber
On Mon, Jan 9, 2012 at 2:22 PM, Isaac Dupree < ml@isaac.cedarswampstudios.org> wrote:
You mean this wiki page, right?: http://hackage.haskell.org/**trac/ghc/wiki/Records/**NameSpacinghttp://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
That is, there are no fundamental
objections to the implementation of this records implementation.
I think that might be overly optimistic... I think there's a risk that SPJ finds an irritating complication to type inference & the rest of us aren't type-system-savvy enough to continue trying to guess at that :) But I think you're referring to whether we object to ad-hoc overloading of record field names (neither parametric nor class-based polymorphism), if no difficulties crop up. Some of the concerns on http://www.haskell.org/** haskellwiki/**TypeDirectedNameResolutionhttp://www.haskell.org/haskellwiki/TypeDirectedNameResolutionapply -- I'm not sure to what extent, but address those concerns rather than require those people to repeat themselves again! :)
(If we dodge all those obstacles, well, a better record system is better!)
This shouldn't complicate type inference (other than the fact that we must avoid a left-right bias?) because the record field names are not overloaded - instead it puts some burden back on the user to add more type annotations. The difficult aspect of TDNR was that it was assuming overloading - although there is really no reason why it can't instead assume name-spacing. TDNR and this record proposal share many of the same syntax issues you list. Thanks for the detailed feedback! I am travelling right now, will review when I get a chance.
Greg Weber

On 01/10/2012 05:06 AM, Greg Weber wrote:
Some of your comments seem to not fully recognize the name-spacing (plus simple type resolution) aspect of this proposal that I probably didn't explain well enough. Or maybe I don't understand your comments.
For record.field, field is under the record's namespace. A namespace (from a module or under the new system a record), cannot export conflicting names, and there this system prevents the importer from every having a conflict with a record field name because the field is still under the record's namespace when imported. The type system must resolve the type of the record, and generally the field cannot contribute to this effort.
(I have only used Haskell for several years, not implemented Haskell several times; apologies for my amateurish understanding of the type system.) So Type inference proceeds assuming that "record.field" is something equivalent to "undefined record" (using "undefined" as a function type), and the program is only correct if the type of "record" resolves to a concrete type? I don't know if "concrete type" is at all the right terminology; I mean a type-variable doesn't count (whether class-constrained, "Num a => a", or not, "a", or even "m Int" is not concrete). Is "forall a. Maybe a" okay (if Maybe were a record)? "forall a. Num a => Maybe a"? I'm guessing "yes". Does it get harder in the presence of the type-system extensions? "(a ~ SomeRecord) => a": presumably that works with record syntax? Can the compiler always figure out whether or not it can find a type-variable's concrete type? My concept of Haskell is that (except for Template Haskell), scope resolution happens before type inference happens, no exceptions. So you're deliberately breaking that pattern. Right? Does this order of stages (regular scope selection, then type inference, then record scope) make as high a fraction of code work as Frege's left-to-right model (which I am guessing interleaves type inference and record scope selection as it proceeds left-to-right through the program)? Correct me if I got something wrong, -Isaac

I added your relevant previous notes to the wiki page. I have no idea if what you said about type inference is right or wrong. I don't think that record fields can be called scope resolution in a normal sense - the scope is guaranteed to resolve without conflict (unless the user incorrectly types the field name). We do need those very familiar with the GHC internals to weigh in with any implementation objections. On Tue, Jan 10, 2012 at 11:42 PM, Isaac Dupree < ml@isaac.cedarswampstudios.org> wrote:
On 01/10/2012 05:06 AM, Greg Weber wrote:
Some of your comments seem to not fully recognize the name-spacing (plus simple type resolution) aspect of this proposal that I probably didn't explain well enough. Or maybe I don't understand your comments.
For record.field, field is under the record's namespace. A namespace (from a module or under the new system a record), cannot export conflicting names, and there this system prevents the importer from every having a conflict with a record field name because the field is still under the record's namespace when imported. The type system must resolve the type of the record, and generally the field cannot contribute to this effort.
(I have only used Haskell for several years, not implemented Haskell several times; apologies for my amateurish understanding of the type system.)
So Type inference proceeds assuming that "record.field" is something equivalent to "undefined record" (using "undefined" as a function type), and the program is only correct if the type of "record" resolves to a concrete type? I don't know if "concrete type" is at all the right terminology; I mean a type-variable doesn't count (whether class-constrained, "Num a => a", or not, "a", or even "m Int" is not concrete). Is "forall a. Maybe a" okay (if Maybe were a record)? "forall a. Num a => Maybe a"? I'm guessing "yes". Does it get harder in the presence of the type-system extensions? "(a ~ SomeRecord) => a": presumably that works with record syntax? Can the compiler always figure out whether or not it can find a type-variable's concrete type?
My concept of Haskell is that (except for Template Haskell), scope resolution happens before type inference happens, no exceptions. So you're deliberately breaking that pattern. Right?
Does this order of stages (regular scope selection, then type inference, then record scope) make as high a fraction of code work as Frege's left-to-right model (which I am guessing interleaves type inference and record scope selection as it proceeds left-to-right through the program)?
Correct me if I got something wrong,
-Isaac

Am 11. Januar 2012 08:42 schrieb Isaac Dupree < ml@isaac.cedarswampstudios.org>:
On 01/10/2012 05:06 AM, Greg Weber wrote:
Some of your comments seem to not fully recognize the name-spacing (plus simple type resolution) aspect of this proposal that I probably didn't explain well enough. Or maybe I don't understand your comments.
For record.field, field is under the record's namespace. A namespace (from a module or under the new system a record), cannot export conflicting names, and there this system prevents the importer from every having a conflict with a record field name because the field is still under the record's namespace when imported. The type system must resolve the type of the record, and generally the field cannot contribute to this effort.
(I have only used Haskell for several years, not implemented Haskell several times; apologies for my amateurish understanding of the type system.)
So Type inference proceeds assuming that "record.field" is something equivalent to "undefined record" (using "undefined" as a function type), and the program is only correct if the type of "record" resolves to a concrete type? I don't know if "concrete type" is at all the right terminology; I mean a type-variable doesn't count (whether class-constrained, "Num a => a", or not, "a", or even "m Int" is not concrete). Is "forall a. Maybe a" okay (if Maybe were a record)? "forall a. Num a => Maybe a"? I'm guessing "yes".
Exactly. More specific, the type must be of the form T a1 ... an, where T is a type constructor. The a_i are not needed for field selection, but of course *if* a field is found in namespace T, and the construct was r.f then the type checker is going to check (T.f r), hence the type of r must fit the first argument of T.f in the usual way. The type of T.f itself is of course already known (just like that of any other function the currently typechecked function depends on).
Does this order of stages (regular scope selection, then type inference, then record scope) make as high a fraction of code work as Frege's left-to-right model (which I am guessing interleaves type inference and record scope selection as it proceeds left-to-right through the program)?
I think that the way it is done in the current Frege compiler (note that the language does not prescribe any particular order or way of typechecking) is the one with the worst percentage of "hits", because it's the most simple approach. -- Ingo

On 09/01/2012, Isaac Dupree
You mean this wiki page, right?: http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
That is, there are no fundamental objections to the implementation of this records implementation.
I think that might be overly optimistic... I think there's a risk that SPJ finds an irritating complication to type inference & the rest of us aren't type-system-savvy enough to continue trying to guess at that :) But I think you're referring to whether we object to ad-hoc overloading of record field names (neither parametric nor class-based polymorphism), if no difficulties crop up. Some of the concerns on http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply -- I'm not sure to what extent, but address those concerns rather than require those people to repeat themselves again! :)
(If we dodge all those obstacles, well, a better record system is better!)
Regardless, I think the proposal needs more precision, so I tried for syntax. And got this thousand word email just about syntax, in several sections of reasoning, sorry!
--so here are my conclusions/suggestions up front in case you prefer, most complicated first - look later for details in a different order, referenced by [number].
Given that type inference for expr.field decides between several different possible meanings of "field", which "field"s in scope count as possibilities? I concluded "All identifiers 'field' in top-level scope (i.e. declared in this module or imported unqualified from another module), but no local let/lambda bindings." [1]
I have an unrelated record/module system tweak suggestion to prevent leaks of the field-ness of exports meant only as functions. [2]
".field", for any identifier "field", is a postfix operator that binds more tightly than function application. [1]
I don't care whether the expression and ".field" are permitted to be separated by whitespace or not. [4]
"(.field)" as a section: should it always require parentheses? (assuming there is a way to type-inference the unapplied dot operator usefully at all). [3]
The Type.{...} / expr.{...} variations look probably fine ("Syntax for updates" in the wiki). [5]
Allow "TyCon.field" for selecting a specific version of "field", but only if there isn't a module in scope as "TyCon" in which case it's interpreted as "Module.field". [7]
Allow "expr.TyCon.field" / "expr.Module.field" wherever "expr.field" is allowed. [8]
I bikesheddily suggest "field@expr" rather than "expr.field" (I'd be alright with either/both). [6]
===== Defining the basic dot syntax for record field selection =====
[1] .x, for any identifier x, is a postfix operator that binds more tightly than function application. This operator does not constrain the type of its operand or its result. After regular type inference, the type system collects in-scope "x"s and does something to try to choose one.
(As a non-type-system-expert, I'm not addressing what "does something" means in this email, besides capitalizing TYPE INFERENCE where I suspect there might (or might not) be extra problems. Anyway, I wish the algorithm do the right thing for "expr.x.y.z".)
But which in-scope "x"es does it collect? Regular Haskell scope would completely break "let x = var.x" if we wished to allow "let x = var.x".
How about: all record fields 'x' declared in this module or imported (qualified[??] or unqualified) from another module.
[[[ Should qualified ones be allowed? Pro: if you import Data.Map qualified, as is common (let's just pretend that Maps have members), then someMap.field works.
Pro: it's like allowing qualified imports for instance declaration class-member-definitions.
Con: it's not really like that. It makes qualified imports a weaker protection, as the class/instance exception can lead to no ambiguity, but this can lead to ambiguity. The PVP would make a sad face.
Con: using unqualified import with (..) would easily bring the field names into scope. Fictitiously, "import qualified Data.Map as Map; import Data.Map(Map(..))".
Observation: allowing qualified imports, but not following the class/instance system's style of including everything in the transitive closure of imported modules, still prevents you (Pro) from breaking intentional abstraction barriers, but (Con?) requires you to import the operators for types you receive but don't import.
Opinion: only unqualified imports should be part of the selection process. ]]]
[[[ Problem: Restricting the selection to only record fields further compromises an existing imperfect property of Haskell: module Library (Type, constructor, deconstructor) where data Type = Constructor { deconstructor :: Int } -- let's pretend it's a bounds-limited int or such. constructor int | int >= 3 && int < 17 = Constructor int
Currently, importers of the module can observe that 'deconstructor' is a record-field by importing Library(Type(..)) and getting 'deconstructor' (see [2]--can we change that.). This makes it slightly harder for the library implementer to change that name to a non-record-field. In the proposal, the users might also have gotten used to "expr.deconstructor", and there would be no way to replace that syntax.
Possible fix: also require all the type's data-constructors to be in scope. I think that's too big a hammer though. We could punt. We could change the selection to "all top-level names 'x' declared in this module or imported unqualified from another module."
Opinion: "all top-level names 'x' declared in this module or imported unqualified from another module." is better and not worse than restricting it to record-fields (provided that it does not burden the type inferencer complexity).
Problem: Given that, it's annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. Possible solution: allow "let .deconstruct = \x -> x - 100", possibly with sugary variations. Possibly require a type-signature. Possibility: also allow ".deconstruct = " at top level. (If the dot notation does funny things with TYPE INFERENCE, this might be a dubious idea.) Possible solution: consider *both* local bindings *and* the top-level names that they would normally shadow. (That sounds rather odd; it might work since most of the local bindings with those names will be non-functions and thus not eligible; is it worth it?) Opinion: Just let it be annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. (You can't declare data or classes in let bindings either. Any of these can be improved but I don't think we need to just to have a record system.)
[2] We could make this leak fixable thus:
"module Library (Type, deconstructor)" does not make "import Library(Type(..))" import "deconstructor" but "module Library (Type(deconstructor))" or "module Library (Type(..))" do make "import Library(Type(..))" import "deconstructor" (and make "import Library(Type(deconstructor))" valid).
The difference could even extend to not making "deconstructor" usable in any record syntax (construction, pattern matching, and record update) unless it's imported from somewhere that it's exported syntactically under its type.
This might make existing code break. Does anyone think this change might be a good idea? ]]]
Suggestion: select all identifiers 'x' in top-level scope (i.e. declared in this module or imported unqualified from another module).
===== Miscellaneous dot-syntax observations =====
[3] Observation: The point-free thought "b . .a" would be exactly the same as the "b . a" we have now with record fields -- except that it behaves a bit differently regarding scope/TYPE INFERENCE. It implies that (.a) is a section of the unary postfix record-field-selection operator (similar to (1 +) being an operator section). "b . .a" also suggests not requiring parentheses for that section when parsing precedence would not require it... for example, parsing precedence would require it in "map (.a) list" if "map .a list" meant "(map.a) list".
[4] Should "identifier .field" be disallowed because it's almost certainly a mistake? But " (some long expression here) .field " probably isn't a mistake, so, shrugs. I think it would be equally plausible to require the non-section version of dot to have no spaces on either side, or only require no-space on the right hand side of the dot.
[5] The "Syntax for updates" from Frege in the wiki looks fine and syntactically unambiguous to me ("identifier.{" without spaces) - I'd want to think about it later but it seems unlikely to me to go terribly wrong. When you say "If a::T then a.{x=} and a.{x=42} are valid", okay they're valid but as what? as "T.{x=} a" and "T.{x=42} a", or without the "a" argument? e.g. say "If a::T then a.{x=} and a.{x=42} are equivalent to (T.{x=} a) and (T.{x=42} a)". Does TYPE INFERENCE have any more trouble with those than with regular field selection (I don't know)?
On January 8th, 2012 CE, I wrote:
Perhaps we could use let-syntax, thus: let { r.x = x'; r.y = y'; r.z = z'; } in r
If we allow tuples of selectors, thus: r.(x, y, z) = (r.x, r.y, r.z) then one can simply write let r.(x, y, z) = (x', y', z') in r
I once more propose this syntax (or the like).
Thus the language would be simpler (little/no new syntax to define),
and it would keep to the principle of Least Surprise (little/no new
syntax to learn).
I have not seen any comments on this – is there any consent? dissent?
On 09/01/2012, Isaac Dupree
[6] If we want to bikeshed about what the operator should be ("." or other) : As http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio... says about using dot, "It's standard practice, and that counts for a lot." But if we want to bikeshed and look for an operator that orders things the same way as function application and composition... record.field vs field@record . "@" is already reserved. It could bind more tightly than function application and type-inference differently. Because it's reserved, it doesn't need to require no-spaces-around-it. Here's example from that TDNR page: typical OO: "x.f(3).g(v,w).h" how it would have to be in Haskell+TDNR-dot-syntax: "((x.f 3).g v w).h" or with @ instead of .: "h@(g@(f@x 3) v w)" Which is IMHO only minorly better... but then again, the Frege-ish record proposal might only be doing TDNR for records specifically. (more syntax and semantic discussion at http://www.haskell.org/haskellwiki/TypeDirectedNameResolution ).
...I kind of like @, but think it's a bikeshed: I claim that, if we work out the semantics (big "if"!), that not enough of us are going to say "it's better to have no records than dot-syntax records" [ditto for every other syntax] that the best decision would be "no records!". If this becomes a popular bikeshed, we might just try straw-polling and picking what's popular (rather than get distracted and waste a year -- a common discussion outcome!). (Though, feelings might be stronger than most bikesheds, for such a core language + syntax change...hmm.)
===== Module-related stuff =====
It would be permitted to declare two records in the same scope with the same record field name.
GHC would not warn if you shadow record field names with lambda/let-bound variables (It currently does, quite reasonably, warn, iff you enabled -fwarn-name-shadowing && not -XNamedFieldPuns.) This, along with all the other changes, would be contingent on a new flag like -XNamedFieldDots.
[7] We would add a syntax "TyCon.name".
Thorough option for TyCon.name: (1) If there is a module in scope as TyCon containing a type TyCon with a field "name", it would choose that field. (2) Else if there is a module import in scope as TyCon containing an unqualified, unambiguous* identifier "name", it would choose that. *["unambiguous" meaning it doesn't have two different records with exported fields named "name".] (3) Else if there is a type-constructor in scope TyCon with a named-field "name", it would choose that. (4) Else it would be an error.
I think rule (1) can be deleted without changing anything.
People usually use module names with dots in them, and type-constructors cannot have dots in them. If a single module decides to import one module "as" the exact name of a type imported from an entirely different module, and the two happen to have some of the same identifiers, perhaps it's okay for silliness to ensue. In fact, given the unlikeliness of inconsistent overlaps like that, I suspect that:
Simple option: (1) if there's a module in scope of that name, it means module scope even if that means the lookup fails (2) if there's not a module, see if it can be a type name
is equally fine and better because it's simpler. IMHO we shouldn't put these two rules in the other order because it has the ability to break existing code only for the benefit of something that hardly matters either way at all.
None of these changes can break existing code. The only breaking change that "-XNamedFieldDots" would introduce is a different meaning of a dot followed without spaces by a lowercase letter.
[8] I suggest we should allow expr.TyCon.field (and expr.Module.field I guess) for field-selection too. It's irritating when a syntax can't be qualified without rearranging things (to e.g. "(TyCon.field expr)" or e.g. "(expr::TyCon Int).field" [for single-parameter TyCons like Maybe]).
There is no specific interaction with type-classes because Haskell type-classes do not behave like Frege type-classes (as best I can tell from this discussion).
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I added this and your Control.Category.<<< to the wiki.
I am not sure about the tuple proposal - tuples normally imply an ordering,
which would imply that all record fields must be accounted for at least
with an empty comma or an underscore, particularly if updating the last
field in a record. For records we want a syntax where we can pick out one
or many fields to update and ignore the rest.
My feeling on <<< is that <~ is slightly more intuitive than <<< because it
looks like an arrow which I equate with functions, and <<< is more
difficult to parse because I have to recognize three in a row of the same
character . However, if everyone likes using the unicode dot, then it
doesn't matter what the non-unicode symbol is, and re-using existing
symbols is certainly advantageous.
On Thu, Jan 12, 2012 at 10:02 AM, Matthew Farkas-Dyck
You mean this wiki page, right?: http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
That is, there are no fundamental objections to the implementation of this records implementation.
I think that might be overly optimistic... I think there's a risk that SPJ finds an irritating complication to type inference & the rest of us aren't type-system-savvy enough to continue trying to guess at that :) But I think you're referring to whether we object to ad-hoc overloading of record field names (neither parametric nor class-based polymorphism), if no difficulties crop up. Some of the concerns on http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply -- I'm not sure to what extent, but address those concerns rather than require those people to repeat themselves again! :)
(If we dodge all those obstacles, well, a better record system is better!)
Regardless, I think the proposal needs more precision, so I tried for syntax. And got this thousand word email just about syntax, in several sections of reasoning, sorry!
--so here are my conclusions/suggestions up front in case you prefer, most complicated first - look later for details in a different order, referenced by [number].
Given that type inference for expr.field decides between several different possible meanings of "field", which "field"s in scope count as possibilities? I concluded "All identifiers 'field' in top-level scope (i.e. declared in this module or imported unqualified from another module), but no local let/lambda bindings." [1]
I have an unrelated record/module system tweak suggestion to prevent leaks of the field-ness of exports meant only as functions. [2]
".field", for any identifier "field", is a postfix operator that binds more tightly than function application. [1]
I don't care whether the expression and ".field" are permitted to be separated by whitespace or not. [4]
"(.field)" as a section: should it always require parentheses? (assuming there is a way to type-inference the unapplied dot operator usefully at all). [3]
The Type.{...} / expr.{...} variations look probably fine ("Syntax for updates" in the wiki). [5]
Allow "TyCon.field" for selecting a specific version of "field", but only if there isn't a module in scope as "TyCon" in which case it's interpreted as "Module.field". [7]
Allow "expr.TyCon.field" / "expr.Module.field" wherever "expr.field" is allowed. [8]
I bikesheddily suggest "field@expr" rather than "expr.field" (I'd be alright with either/both). [6]
===== Defining the basic dot syntax for record field selection =====
[1] .x, for any identifier x, is a postfix operator that binds more tightly than function application. This operator does not constrain the type of its operand or its result. After regular type inference, the type system collects in-scope "x"s and does something to try to choose one.
(As a non-type-system-expert, I'm not addressing what "does something" means in this email, besides capitalizing TYPE INFERENCE where I suspect there might (or might not) be extra problems. Anyway, I wish the algorithm do the right thing for "expr.x.y.z".)
But which in-scope "x"es does it collect? Regular Haskell scope would completely break "let x = var.x" if we wished to allow "let x = var.x".
How about: all record fields 'x' declared in this module or imported (qualified[??] or unqualified) from another module.
[[[ Should qualified ones be allowed? Pro: if you import Data.Map qualified, as is common (let's just pretend that Maps have members), then someMap.field works.
Pro: it's like allowing qualified imports for instance declaration class-member-definitions.
Con: it's not really like that. It makes qualified imports a weaker protection, as the class/instance exception can lead to no ambiguity, but this can lead to ambiguity. The PVP would make a sad face.
Con: using unqualified import with (..) would easily bring the field names into scope. Fictitiously, "import qualified Data.Map as Map; import Data.Map(Map(..))".
Observation: allowing qualified imports, but not following the class/instance system's style of including everything in the transitive closure of imported modules, still prevents you (Pro) from breaking intentional abstraction barriers, but (Con?) requires you to import the operators for types you receive but don't import.
Opinion: only unqualified imports should be part of the selection
On 09/01/2012, Isaac Dupree
wrote: process. ]]]
[[[ Problem: Restricting the selection to only record fields further compromises an existing imperfect property of Haskell: module Library (Type, constructor, deconstructor) where data Type = Constructor { deconstructor :: Int } -- let's pretend it's a bounds-limited int or such. constructor int | int >= 3 && int < 17 = Constructor int
Currently, importers of the module can observe that 'deconstructor' is a record-field by importing Library(Type(..)) and getting 'deconstructor' (see [2]--can we change that.). This makes it slightly harder for the library implementer to change that name to a non-record-field. In the proposal, the users might also have gotten used to "expr.deconstructor", and there would be no way to replace that syntax.
Possible fix: also require all the type's data-constructors to be in scope. I think that's too big a hammer though. We could punt. We could change the selection to "all top-level names 'x' declared in this module or imported unqualified from another module."
Opinion: "all top-level names 'x' declared in this module or imported unqualified from another module." is better and not worse than restricting it to record-fields (provided that it does not burden the type inferencer complexity).
Problem: Given that, it's annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. Possible solution: allow "let .deconstruct = \x -> x - 100", possibly with sugary variations. Possibly require a type-signature. Possibility: also allow ".deconstruct = " at top level. (If the dot notation does funny things with TYPE INFERENCE, this might be a dubious idea.) Possible solution: consider *both* local bindings *and* the top-level names that they would normally shadow. (That sounds rather odd; it might work since most of the local bindings with those names will be non-functions and thus not eligible; is it worth it?) Opinion: Just let it be annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. (You can't declare data or classes in let bindings either. Any of these can be improved but I don't think we need to just to have a record system.)
[2] We could make this leak fixable thus:
"module Library (Type, deconstructor)" does not make "import Library(Type(..))" import "deconstructor" but "module Library (Type(deconstructor))" or "module Library (Type(..))" do make "import Library(Type(..))" import "deconstructor" (and make "import Library(Type(deconstructor))" valid).
The difference could even extend to not making "deconstructor" usable in any record syntax (construction, pattern matching, and record update) unless it's imported from somewhere that it's exported syntactically under its type.
This might make existing code break. Does anyone think this change might be a good idea? ]]]
Suggestion: select all identifiers 'x' in top-level scope (i.e. declared in this module or imported unqualified from another module).
===== Miscellaneous dot-syntax observations =====
[3] Observation: The point-free thought "b . .a" would be exactly the same as the "b . a" we have now with record fields -- except that it behaves a bit differently regarding scope/TYPE INFERENCE. It implies that (.a) is a section of the unary postfix record-field-selection operator (similar to (1 +) being an operator section). "b . .a" also suggests not requiring parentheses for that section when parsing precedence would not require it... for example, parsing precedence would require it in "map (.a) list" if "map .a list" meant "(map.a) list".
[4] Should "identifier .field" be disallowed because it's almost certainly a mistake? But " (some long expression here) .field " probably isn't a mistake, so, shrugs. I think it would be equally plausible to require the non-section version of dot to have no spaces on either side, or only require no-space on the right hand side of the dot.
[5] The "Syntax for updates" from Frege in the wiki looks fine and syntactically unambiguous to me ("identifier.{" without spaces) - I'd want to think about it later but it seems unlikely to me to go terribly wrong. When you say "If a::T then a.{x=} and a.{x=42} are valid", okay they're valid but as what? as "T.{x=} a" and "T.{x=42} a", or without the "a" argument? e.g. say "If a::T then a.{x=} and a.{x=42} are equivalent to (T.{x=} a) and (T.{x=42} a)". Does TYPE INFERENCE have any more trouble with those than with regular field selection (I don't know)?
On January 8th, 2012 CE, I wrote:
Perhaps we could use let-syntax, thus: let { r.x = x'; r.y = y'; r.z = z'; } in r
If we allow tuples of selectors, thus: r.(x, y, z) = (r.x, r.y, r.z) then one can simply write let r.(x, y, z) = (x', y', z') in r
I once more propose this syntax (or the like). Thus the language would be simpler (little/no new syntax to define), and it would keep to the principle of Least Surprise (little/no new syntax to learn). I have not seen any comments on this – is there any consent? dissent?
On 09/01/2012, Isaac Dupree
wrote: [6] If we want to bikeshed about what the operator should be ("." or other) : As
http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio...
says about using dot, "It's standard practice, and that counts for a lot." But if we want to bikeshed and look for an operator that orders things the same way as function application and composition... record.field vs field@record . "@" is already reserved. It could bind more tightly than function application and type-inference differently. Because it's reserved, it doesn't need to require no-spaces-around-it. Here's example from that TDNR page: typical OO: "x.f(3).g(v,w).h" how it would have to be in Haskell+TDNR-dot-syntax: "((x.f 3).g v w).h" or with @ instead of .: "h@(g@(f@x 3) v w)" Which is IMHO only minorly better... but then again, the Frege-ish record proposal might only be doing TDNR for records specifically. (more syntax and semantic discussion at http://www.haskell.org/haskellwiki/TypeDirectedNameResolution ).
...I kind of like @, but think it's a bikeshed: I claim that, if we work out the semantics (big "if"!), that not enough of us are going to say "it's better to have no records than dot-syntax records" [ditto for every other syntax] that the best decision would be "no records!". If this becomes a popular bikeshed, we might just try straw-polling and picking what's popular (rather than get distracted and waste a year -- a common discussion outcome!). (Though, feelings might be stronger than most bikesheds, for such a core language + syntax change...hmm.)
===== Module-related stuff =====
It would be permitted to declare two records in the same scope with the same record field name.
GHC would not warn if you shadow record field names with lambda/let-bound variables (It currently does, quite reasonably, warn, iff you enabled -fwarn-name-shadowing && not -XNamedFieldPuns.) This, along with all the other changes, would be contingent on a new flag like -XNamedFieldDots.
[7] We would add a syntax "TyCon.name".
Thorough option for TyCon.name: (1) If there is a module in scope as TyCon containing a type TyCon with a field "name", it would choose that field. (2) Else if there is a module import in scope as TyCon containing an unqualified, unambiguous* identifier "name", it would choose that. *["unambiguous" meaning it doesn't have two different records with exported fields named "name".] (3) Else if there is a type-constructor in scope TyCon with a named-field "name", it would choose that. (4) Else it would be an error.
I think rule (1) can be deleted without changing anything.
People usually use module names with dots in them, and type-constructors cannot have dots in them. If a single module decides to import one module "as" the exact name of a type imported from an entirely different module, and the two happen to have some of the same identifiers, perhaps it's okay for silliness to ensue. In fact, given the unlikeliness of inconsistent overlaps like that, I suspect that:
Simple option: (1) if there's a module in scope of that name, it means module scope even if that means the lookup fails (2) if there's not a module, see if it can be a type name
is equally fine and better because it's simpler. IMHO we shouldn't put these two rules in the other order because it has the ability to break existing code only for the benefit of something that hardly matters either way at all.
None of these changes can break existing code. The only breaking change that "-XNamedFieldDots" would introduce is a different meaning of a dot followed without spaces by a lowercase letter.
[8] I suggest we should allow expr.TyCon.field (and expr.Module.field I guess) for field-selection too. It's irritating when a syntax can't be qualified without rearranging things (to e.g. "(TyCon.field expr)" or e.g. "(expr::TyCon Int).field" [for single-parameter TyCons like Maybe]).
There is no specific interaction with type-classes because Haskell type-classes do not behave like Frege type-classes (as best I can tell from this discussion).
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Thu, Jan 12, 2012 at 2:23 PM, Greg Weber
I added this and your Control.Category.<<< to the wiki.
I am not sure about the tuple proposal - tuples normally imply an ordering, which would imply that all record fields must be accounted for at least with an empty comma or an underscore, particularly if updating the last field in a record. For records we want a syntax where we can pick out one or many fields to update and ignore the rest.
My feeling on <<< is that <~ is slightly more intuitive than <<< because it looks like an arrow which I equate with functions, and <<< is more difficult to parse because I have to recognize three in a row of the same character . However, if everyone likes using the unicode dot, then it doesn't matter what the non-unicode symbol is, and re-using existing symbols is certainly advantageous.
I like <<< better than <~. My extremely well-founded reasoning is that <~ looks weird. Unfortunately, (.) is nicer still. Unicode dot would be the nicest but I have no idea how to type it other than by copy-paste. What about &? I don't think it's used anywhere significant, and it also has a nice mnemonic, "and". (You have to read it backwards, but that's a pre-existing condition...)
On Thu, Jan 12, 2012 at 10:02 AM, Matthew Farkas-Dyck
wrote: On 09/01/2012, Isaac Dupree
wrote: You mean this wiki page, right?: http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
That is, there are no fundamental objections to the implementation of this records implementation.
I think that might be overly optimistic... I think there's a risk that SPJ finds an irritating complication to type inference & the rest of us aren't type-system-savvy enough to continue trying to guess at that :) But I think you're referring to whether we object to ad-hoc overloading of record field names (neither parametric nor class-based polymorphism), if no difficulties crop up. Some of the concerns on http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply -- I'm not sure to what extent, but address those concerns rather than require those people to repeat themselves again! :)
(If we dodge all those obstacles, well, a better record system is better!)
Regardless, I think the proposal needs more precision, so I tried for syntax. And got this thousand word email just about syntax, in several sections of reasoning, sorry!
--so here are my conclusions/suggestions up front in case you prefer, most complicated first - look later for details in a different order, referenced by [number].
Given that type inference for expr.field decides between several different possible meanings of "field", which "field"s in scope count as possibilities? I concluded "All identifiers 'field' in top-level scope (i.e. declared in this module or imported unqualified from another module), but no local let/lambda bindings." [1]
I have an unrelated record/module system tweak suggestion to prevent leaks of the field-ness of exports meant only as functions. [2]
".field", for any identifier "field", is a postfix operator that binds more tightly than function application. [1]
I don't care whether the expression and ".field" are permitted to be separated by whitespace or not. [4]
"(.field)" as a section: should it always require parentheses? (assuming there is a way to type-inference the unapplied dot operator usefully at all). [3]
The Type.{...} / expr.{...} variations look probably fine ("Syntax for updates" in the wiki). [5]
Allow "TyCon.field" for selecting a specific version of "field", but only if there isn't a module in scope as "TyCon" in which case it's interpreted as "Module.field". [7]
Allow "expr.TyCon.field" / "expr.Module.field" wherever "expr.field" is allowed. [8]
I bikesheddily suggest "field@expr" rather than "expr.field" (I'd be alright with either/both). [6]
===== Defining the basic dot syntax for record field selection =====
[1] .x, for any identifier x, is a postfix operator that binds more tightly than function application. This operator does not constrain the type of its operand or its result. After regular type inference, the type system collects in-scope "x"s and does something to try to choose one.
(As a non-type-system-expert, I'm not addressing what "does something" means in this email, besides capitalizing TYPE INFERENCE where I suspect there might (or might not) be extra problems. Anyway, I wish the algorithm do the right thing for "expr.x.y.z".)
But which in-scope "x"es does it collect? Regular Haskell scope would completely break "let x = var.x" if we wished to allow "let x = var.x".
How about: all record fields 'x' declared in this module or imported (qualified[??] or unqualified) from another module.
[[[ Should qualified ones be allowed? Pro: if you import Data.Map qualified, as is common (let's just pretend that Maps have members), then someMap.field works.
Pro: it's like allowing qualified imports for instance declaration class-member-definitions.
Con: it's not really like that. It makes qualified imports a weaker protection, as the class/instance exception can lead to no ambiguity, but this can lead to ambiguity. The PVP would make a sad face.
Con: using unqualified import with (..) would easily bring the field names into scope. Fictitiously, "import qualified Data.Map as Map; import Data.Map(Map(..))".
Observation: allowing qualified imports, but not following the class/instance system's style of including everything in the transitive closure of imported modules, still prevents you (Pro) from breaking intentional abstraction barriers, but (Con?) requires you to import the operators for types you receive but don't import.
Opinion: only unqualified imports should be part of the selection process. ]]]
[[[ Problem: Restricting the selection to only record fields further compromises an existing imperfect property of Haskell: module Library (Type, constructor, deconstructor) where data Type = Constructor { deconstructor :: Int } -- let's pretend it's a bounds-limited int or such. constructor int | int >= 3 && int < 17 = Constructor int
Currently, importers of the module can observe that 'deconstructor' is a record-field by importing Library(Type(..)) and getting 'deconstructor' (see [2]--can we change that.). This makes it slightly harder for the library implementer to change that name to a non-record-field. In the proposal, the users might also have gotten used to "expr.deconstructor", and there would be no way to replace that syntax.
Possible fix: also require all the type's data-constructors to be in scope. I think that's too big a hammer though. We could punt. We could change the selection to "all top-level names 'x' declared in this module or imported unqualified from another module."
Opinion: "all top-level names 'x' declared in this module or imported unqualified from another module." is better and not worse than restricting it to record-fields (provided that it does not burden the type inferencer complexity).
Problem: Given that, it's annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. Possible solution: allow "let .deconstruct = \x -> x - 100", possibly with sugary variations. Possibly require a type-signature. Possibility: also allow ".deconstruct = " at top level. (If the dot notation does funny things with TYPE INFERENCE, this might be a dubious idea.) Possible solution: consider *both* local bindings *and* the top-level names that they would normally shadow. (That sounds rather odd; it might work since most of the local bindings with those names will be non-functions and thus not eligible; is it worth it?) Opinion: Just let it be annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. (You can't declare data or classes in let bindings either. Any of these can be improved but I don't think we need to just to have a record system.)
[2] We could make this leak fixable thus:
"module Library (Type, deconstructor)" does not make "import Library(Type(..))" import "deconstructor" but "module Library (Type(deconstructor))" or "module Library (Type(..))" do make "import Library(Type(..))" import "deconstructor" (and make "import Library(Type(deconstructor))" valid).
The difference could even extend to not making "deconstructor" usable in any record syntax (construction, pattern matching, and record update) unless it's imported from somewhere that it's exported syntactically under its type.
This might make existing code break. Does anyone think this change might be a good idea? ]]]
Suggestion: select all identifiers 'x' in top-level scope (i.e. declared in this module or imported unqualified from another module).
===== Miscellaneous dot-syntax observations =====
[3] Observation: The point-free thought "b . .a" would be exactly the same as the "b . a" we have now with record fields -- except that it behaves a bit differently regarding scope/TYPE INFERENCE. It implies that (.a) is a section of the unary postfix record-field-selection operator (similar to (1 +) being an operator section). "b . .a" also suggests not requiring parentheses for that section when parsing precedence would not require it... for example, parsing precedence would require it in "map (.a) list" if "map .a list" meant "(map.a) list".
[4] Should "identifier .field" be disallowed because it's almost certainly a mistake? But " (some long expression here) .field " probably isn't a mistake, so, shrugs. I think it would be equally plausible to require the non-section version of dot to have no spaces on either side, or only require no-space on the right hand side of the dot.
[5] The "Syntax for updates" from Frege in the wiki looks fine and syntactically unambiguous to me ("identifier.{" without spaces) - I'd want to think about it later but it seems unlikely to me to go terribly wrong. When you say "If a::T then a.{x=} and a.{x=42} are valid", okay they're valid but as what? as "T.{x=} a" and "T.{x=42} a", or without the "a" argument? e.g. say "If a::T then a.{x=} and a.{x=42} are equivalent to (T.{x=} a) and (T.{x=42} a)". Does TYPE INFERENCE have any more trouble with those than with regular field selection (I don't know)?
On January 8th, 2012 CE, I wrote:
Perhaps we could use let-syntax, thus: let { r.x = x'; r.y = y'; r.z = z'; } in r
If we allow tuples of selectors, thus: r.(x, y, z) = (r.x, r.y, r.z) then one can simply write let r.(x, y, z) = (x', y', z') in r
I once more propose this syntax (or the like). Thus the language would be simpler (little/no new syntax to define), and it would keep to the principle of Least Surprise (little/no new syntax to learn). I have not seen any comments on this – is there any consent? dissent?
On 09/01/2012, Isaac Dupree
wrote: [6] If we want to bikeshed about what the operator should be ("." or other) : As
http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio... says about using dot, "It's standard practice, and that counts for a lot." But if we want to bikeshed and look for an operator that orders things the same way as function application and composition... record.field vs field@record . "@" is already reserved. It could bind more tightly than function application and type-inference differently. Because it's reserved, it doesn't need to require no-spaces-around-it. Here's example from that TDNR page: typical OO: "x.f(3).g(v,w).h" how it would have to be in Haskell+TDNR-dot-syntax: "((x.f 3).g v w).h" or with @ instead of .: "h@(g@(f@x 3) v w)" Which is IMHO only minorly better... but then again, the Frege-ish record proposal might only be doing TDNR for records specifically. (more syntax and semantic discussion at http://www.haskell.org/haskellwiki/TypeDirectedNameResolution ).
...I kind of like @, but think it's a bikeshed: I claim that, if we work out the semantics (big "if"!), that not enough of us are going to say "it's better to have no records than dot-syntax records" [ditto for every other syntax] that the best decision would be "no records!". If this becomes a popular bikeshed, we might just try straw-polling and picking what's popular (rather than get distracted and waste a year -- a common discussion outcome!). (Though, feelings might be stronger than most bikesheds, for such a core language + syntax change...hmm.)
===== Module-related stuff =====
It would be permitted to declare two records in the same scope with the same record field name.
GHC would not warn if you shadow record field names with lambda/let-bound variables (It currently does, quite reasonably, warn, iff you enabled -fwarn-name-shadowing && not -XNamedFieldPuns.) This, along with all the other changes, would be contingent on a new flag like -XNamedFieldDots.
[7] We would add a syntax "TyCon.name".
Thorough option for TyCon.name: (1) If there is a module in scope as TyCon containing a type TyCon with a field "name", it would choose that field. (2) Else if there is a module import in scope as TyCon containing an unqualified, unambiguous* identifier "name", it would choose that. *["unambiguous" meaning it doesn't have two different records with exported fields named "name".] (3) Else if there is a type-constructor in scope TyCon with a named-field "name", it would choose that. (4) Else it would be an error.
I think rule (1) can be deleted without changing anything.
People usually use module names with dots in them, and type-constructors cannot have dots in them. If a single module decides to import one module "as" the exact name of a type imported from an entirely different module, and the two happen to have some of the same identifiers, perhaps it's okay for silliness to ensue. In fact, given the unlikeliness of inconsistent overlaps like that, I suspect that:
Simple option: (1) if there's a module in scope of that name, it means module scope even if that means the lookup fails (2) if there's not a module, see if it can be a type name
is equally fine and better because it's simpler. IMHO we shouldn't put these two rules in the other order because it has the ability to break existing code only for the benefit of something that hardly matters either way at all.
None of these changes can break existing code. The only breaking change that "-XNamedFieldDots" would introduce is a different meaning of a dot followed without spaces by a lowercase letter.
[8] I suggest we should allow expr.TyCon.field (and expr.Module.field I guess) for field-selection too. It's irritating when a syntax can't be qualified without rearranging things (to e.g. "(TyCon.field expr)" or e.g. "(expr::TyCon Int).field" [for single-parameter TyCons like Maybe]).
There is no specific interaction with type-classes because Haskell type-classes do not behave like Frege type-classes (as best I can tell from this discussion).
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Work is punishment for failing to procrastinate effectively.

On 12/01/2012, Greg Weber
I added this and your Control.Category.<<< to the wiki.
Thanks.
I am not sure about the tuple proposal - tuples normally imply an ordering, which would imply that all record fields must be accounted for at least with an empty comma or an underscore, particularly if updating the last field in a record. For records we want a syntax where we can pick out one or many fields to update and ignore the rest.
Sorry, my proposal was unclear. This is not what I meant; rather, I meant that one could write let r.(x, y) = (x', y') whatever other fields might be in r. I clarify further on the wiki. That said, I notice now that this syntax is quite verbose, far more so than the .{} syntax, which is a loss. I think the brevity worth the added complexity.
My feeling on <<< is that <~ is slightly more intuitive than <<< because it looks like an arrow which I equate with functions, and <<< is more difficult to parse because I have to recognize three in a row of the same character . However, if everyone likes using the unicode dot, then it doesn't matter what the non-unicode symbol is, and re-using existing symbols is certainly advantageous.
On Thu, Jan 12, 2012 at 10:02 AM, Matthew Farkas-Dyck
wrote: You mean this wiki page, right?: http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
That is, there are no fundamental objections to the implementation of this records implementation.
I think that might be overly optimistic... I think there's a risk that SPJ finds an irritating complication to type inference & the rest of us aren't type-system-savvy enough to continue trying to guess at that :) But I think you're referring to whether we object to ad-hoc overloading of record field names (neither parametric nor class-based polymorphism), if no difficulties crop up. Some of the concerns on http://www.haskell.org/haskellwiki/TypeDirectedNameResolution apply -- I'm not sure to what extent, but address those concerns rather than require those people to repeat themselves again! :)
(If we dodge all those obstacles, well, a better record system is better!)
Regardless, I think the proposal needs more precision, so I tried for syntax. And got this thousand word email just about syntax, in several sections of reasoning, sorry!
--so here are my conclusions/suggestions up front in case you prefer, most complicated first - look later for details in a different order, referenced by [number].
Given that type inference for expr.field decides between several different possible meanings of "field", which "field"s in scope count as possibilities? I concluded "All identifiers 'field' in top-level scope (i.e. declared in this module or imported unqualified from another module), but no local let/lambda bindings." [1]
I have an unrelated record/module system tweak suggestion to prevent leaks of the field-ness of exports meant only as functions. [2]
".field", for any identifier "field", is a postfix operator that binds more tightly than function application. [1]
I don't care whether the expression and ".field" are permitted to be separated by whitespace or not. [4]
"(.field)" as a section: should it always require parentheses? (assuming there is a way to type-inference the unapplied dot operator usefully at all). [3]
The Type.{...} / expr.{...} variations look probably fine ("Syntax for updates" in the wiki). [5]
Allow "TyCon.field" for selecting a specific version of "field", but only if there isn't a module in scope as "TyCon" in which case it's interpreted as "Module.field". [7]
Allow "expr.TyCon.field" / "expr.Module.field" wherever "expr.field" is allowed. [8]
I bikesheddily suggest "field@expr" rather than "expr.field" (I'd be alright with either/both). [6]
===== Defining the basic dot syntax for record field selection =====
[1] .x, for any identifier x, is a postfix operator that binds more tightly than function application. This operator does not constrain the type of its operand or its result. After regular type inference, the type system collects in-scope "x"s and does something to try to choose one.
(As a non-type-system-expert, I'm not addressing what "does something" means in this email, besides capitalizing TYPE INFERENCE where I suspect there might (or might not) be extra problems. Anyway, I wish the algorithm do the right thing for "expr.x.y.z".)
But which in-scope "x"es does it collect? Regular Haskell scope would completely break "let x = var.x" if we wished to allow "let x = var.x".
How about: all record fields 'x' declared in this module or imported (qualified[??] or unqualified) from another module.
[[[ Should qualified ones be allowed? Pro: if you import Data.Map qualified, as is common (let's just pretend that Maps have members), then someMap.field works.
Pro: it's like allowing qualified imports for instance declaration class-member-definitions.
Con: it's not really like that. It makes qualified imports a weaker protection, as the class/instance exception can lead to no ambiguity, but this can lead to ambiguity. The PVP would make a sad face.
Con: using unqualified import with (..) would easily bring the field names into scope. Fictitiously, "import qualified Data.Map as Map; import Data.Map(Map(..))".
Observation: allowing qualified imports, but not following the class/instance system's style of including everything in the transitive closure of imported modules, still prevents you (Pro) from breaking intentional abstraction barriers, but (Con?) requires you to import the operators for types you receive but don't import.
Opinion: only unqualified imports should be part of the selection
On 09/01/2012, Isaac Dupree
wrote: process. ]]]
[[[ Problem: Restricting the selection to only record fields further compromises an existing imperfect property of Haskell: module Library (Type, constructor, deconstructor) where data Type = Constructor { deconstructor :: Int } -- let's pretend it's a bounds-limited int or such. constructor int | int >= 3 && int < 17 = Constructor int
Currently, importers of the module can observe that 'deconstructor' is a record-field by importing Library(Type(..)) and getting 'deconstructor' (see [2]--can we change that.). This makes it slightly harder for the library implementer to change that name to a non-record-field. In the proposal, the users might also have gotten used to "expr.deconstructor", and there would be no way to replace that syntax.
Possible fix: also require all the type's data-constructors to be in scope. I think that's too big a hammer though. We could punt. We could change the selection to "all top-level names 'x' declared in this module or imported unqualified from another module."
Opinion: "all top-level names 'x' declared in this module or imported unqualified from another module." is better and not worse than restricting it to record-fields (provided that it does not burden the type inferencer complexity).
Problem: Given that, it's annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. Possible solution: allow "let .deconstruct = \x -> x - 100", possibly with sugary variations. Possibly require a type-signature. Possibility: also allow ".deconstruct = " at top level. (If the dot notation does funny things with TYPE INFERENCE, this might be a dubious idea.) Possible solution: consider *both* local bindings *and* the top-level names that they would normally shadow. (That sounds rather odd; it might work since most of the local bindings with those names will be non-functions and thus not eligible; is it worth it?) Opinion: Just let it be annoying that you can't bind a record-field-ish-selector in a let/lambda-binding. (You can't declare data or classes in let bindings either. Any of these can be improved but I don't think we need to just to have a record system.)
[2] We could make this leak fixable thus:
"module Library (Type, deconstructor)" does not make "import Library(Type(..))" import "deconstructor" but "module Library (Type(deconstructor))" or "module Library (Type(..))" do make "import Library(Type(..))" import "deconstructor" (and make "import Library(Type(deconstructor))" valid).
The difference could even extend to not making "deconstructor" usable in any record syntax (construction, pattern matching, and record update) unless it's imported from somewhere that it's exported syntactically under its type.
This might make existing code break. Does anyone think this change might be a good idea? ]]]
Suggestion: select all identifiers 'x' in top-level scope (i.e. declared in this module or imported unqualified from another module).
===== Miscellaneous dot-syntax observations =====
[3] Observation: The point-free thought "b . .a" would be exactly the same as the "b . a" we have now with record fields -- except that it behaves a bit differently regarding scope/TYPE INFERENCE. It implies that (.a) is a section of the unary postfix record-field-selection operator (similar to (1 +) being an operator section). "b . .a" also suggests not requiring parentheses for that section when parsing precedence would not require it... for example, parsing precedence would require it in "map (.a) list" if "map .a list" meant "(map.a) list".
[4] Should "identifier .field" be disallowed because it's almost certainly a mistake? But " (some long expression here) .field " probably isn't a mistake, so, shrugs. I think it would be equally plausible to require the non-section version of dot to have no spaces on either side, or only require no-space on the right hand side of the dot.
[5] The "Syntax for updates" from Frege in the wiki looks fine and syntactically unambiguous to me ("identifier.{" without spaces) - I'd want to think about it later but it seems unlikely to me to go terribly wrong. When you say "If a::T then a.{x=} and a.{x=42} are valid", okay they're valid but as what? as "T.{x=} a" and "T.{x=42} a", or without the "a" argument? e.g. say "If a::T then a.{x=} and a.{x=42} are equivalent to (T.{x=} a) and (T.{x=42} a)". Does TYPE INFERENCE have any more trouble with those than with regular field selection (I don't know)?
On January 8th, 2012 CE, I wrote:
Perhaps we could use let-syntax, thus: let { r.x = x'; r.y = y'; r.z = z'; } in r
If we allow tuples of selectors, thus: r.(x, y, z) = (r.x, r.y, r.z) then one can simply write let r.(x, y, z) = (x', y', z') in r
I once more propose this syntax (or the like). Thus the language would be simpler (little/no new syntax to define), and it would keep to the principle of Least Surprise (little/no new syntax to learn). I have not seen any comments on this – is there any consent? dissent?
On 09/01/2012, Isaac Dupree
wrote: [6] If we want to bikeshed about what the operator should be ("." or other) : As
http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio...
says about using dot, "It's standard practice, and that counts for a lot." But if we want to bikeshed and look for an operator that orders things the same way as function application and composition... record.field vs field@record . "@" is already reserved. It could bind more tightly than function application and type-inference differently. Because it's reserved, it doesn't need to require no-spaces-around-it. Here's example from that TDNR page: typical OO: "x.f(3).g(v,w).h" how it would have to be in Haskell+TDNR-dot-syntax: "((x.f 3).g v w).h" or with @ instead of .: "h@(g@(f@x 3) v w)" Which is IMHO only minorly better... but then again, the Frege-ish record proposal might only be doing TDNR for records specifically. (more syntax and semantic discussion at http://www.haskell.org/haskellwiki/TypeDirectedNameResolution ).
...I kind of like @, but think it's a bikeshed: I claim that, if we work out the semantics (big "if"!), that not enough of us are going to say "it's better to have no records than dot-syntax records" [ditto for every other syntax] that the best decision would be "no records!". If this becomes a popular bikeshed, we might just try straw-polling and picking what's popular (rather than get distracted and waste a year -- a common discussion outcome!). (Though, feelings might be stronger than most bikesheds, for such a core language + syntax change...hmm.)
===== Module-related stuff =====
It would be permitted to declare two records in the same scope with the same record field name.
GHC would not warn if you shadow record field names with lambda/let-bound variables (It currently does, quite reasonably, warn, iff you enabled -fwarn-name-shadowing && not -XNamedFieldPuns.) This, along with all the other changes, would be contingent on a new flag like -XNamedFieldDots.
[7] We would add a syntax "TyCon.name".
Thorough option for TyCon.name: (1) If there is a module in scope as TyCon containing a type TyCon with a field "name", it would choose that field. (2) Else if there is a module import in scope as TyCon containing an unqualified, unambiguous* identifier "name", it would choose that. *["unambiguous" meaning it doesn't have two different records with exported fields named "name".] (3) Else if there is a type-constructor in scope TyCon with a named-field "name", it would choose that. (4) Else it would be an error.
I think rule (1) can be deleted without changing anything.
People usually use module names with dots in them, and type-constructors cannot have dots in them. If a single module decides to import one module "as" the exact name of a type imported from an entirely different module, and the two happen to have some of the same identifiers, perhaps it's okay for silliness to ensue. In fact, given the unlikeliness of inconsistent overlaps like that, I suspect that:
Simple option: (1) if there's a module in scope of that name, it means module scope even if that means the lookup fails (2) if there's not a module, see if it can be a type name
is equally fine and better because it's simpler. IMHO we shouldn't put these two rules in the other order because it has the ability to break existing code only for the benefit of something that hardly matters either way at all.
None of these changes can break existing code. The only breaking change that "-XNamedFieldDots" would introduce is a different meaning of a dot followed without spaces by a lowercase letter.
[8] I suggest we should allow expr.TyCon.field (and expr.Module.field I guess) for field-selection too. It's irritating when a syntax can't be qualified without rearranging things (to e.g. "(TyCon.field expr)" or e.g. "(expr::TyCon Int).field" [for single-parameter TyCons like Maybe]).
There is no specific interaction with type-classes because Haskell type-classes do not behave like Frege type-classes (as best I can tell from this discussion).
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 09/01/2012, Greg Weber
Thank you for all your feedback! I updated the wiki page accordingly.
Let us stop and take note of what this feedback is about: the most convenient syntax for manipulating records, and much of this feedback applies to any records proposal. That is, there are no fundamental objections to the implementation of this records implementation. If you give this kind of general feedback then I assume you are fine with the name-spacing records implementation.
At this point I feel we are largely waiting on feedback from implementers to give the implementation critiques or a green light.
But that does not need to stop us from continuing our discussion of the best syntax for using records. For the left-right, right-left issue, I added a discussion and potential solution through partial application:
Partial application provides a potential solution:
(b . .a) r
So if we have a function f r = b r.a then one can write it points-free:
b . .a
Our longer example from above:
e . d . .c . .b . .a
At first glance it may look odd, but it is starting to grow on me. Let us consider more realistic usage with longer names:
echo . delta . .charlie . .beta . .alpha
Is there are more convenient syntax for this? b <.a Note that a move to a different operator for function composition (discussed in dot operator section) would make things easier to parse:
b <~ .a
where the unicode dot might be even nicer.
I told you so (^_^) Unicode dot (∘) would be optimal, since that's what it's for. If to type '∘' is awkward, then one can use (Control.Category.<<<). We need not (and, in my opinion, should not) define another operator.
On Mon, Jan 9, 2012 at 3:15 AM, wren ng thornton
wrote: quux (y . (foo>.< bar).baz (f . g)) moo It's not that easy to distinguish from quux (y . (foo>.< bar) . baz (f . g)) moo
participants (7)
-
Andriy Polischuk
-
Greg Weber
-
Gábor Lehel
-
Ingo Wechsung
-
Isaac Dupree
-
Matthew Farkas-Dyck
-
wren ng thornton