Type Directed Name Resolution

Type-directed name resolution, as originally proposed for Haskell', has now been proposed for GHC. Obvious benefits of this are that conflicting function names from imported modules can be used without qualification (verbose) or pseudo-Hungarian renaming (verbose, and requires that you control the source, and perform the same renaming in all dependencies). This is important for both readability and programming in the large, particularly where records are concerned, as the duplicate name problem cannot be alleviated with typeclasses, and it is often desirable to have the same field names for many records in the same module. http://hackage.haskell.org/trac/ghc/ticket/4479 http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio...

John Smith
Type-directed name resolution, as originally proposed for Haskell', has now been proposed for GHC. Obvious benefits of this are
Does that mean all the questions have been resolved? Can this be shown to interact sanely with type classes and GADTs, etc? I couldn't find any *answers* when following the links, just more questions. Is the intention still to use the dot for this, and separate the different meanings for this symbol by varying the whitespace around it? -k -- If I haven't seen further, it is by standing in the footprints of giants

I still don't know whether I like this idea or not, but here is the simplest definition I can think of about what it promises. Using TDNR, it will be possible to write the following code: data Foo = Foo { name :: String } data Bar = Bar { name :: String } getName :: Either Foo Bar -> String getName (Left f) = name f getName (Right b) = name b However, currently you cannot: "Multiple declarations of 'name'" There are basically two things you can do to solve this "problem". - Use different names for your functions, a la "fooName, barName". This clutters up your code, and sometimes you may not have access to that part of the code. - Define these 2 data types in different modules and import qualified, a la "Foo.name, Bar.name". One might still think this clutters up your code. In any case, as a programmer you need to resolve which function to use depending on types while defining 'getName'. However compiler has enough information to automate this decision for you. This is not a way to do polymorphism, this is merely a way to allow programmers define more than one function with the same name, but different types. This kinda sounds like what java people think polymorphism is :P -- Ozgur Akgun

On 10 November 2010 10:56, Ozgur Akgun
Using TDNR, it will be possible to write the following code:
data Foo = Foo { name :: String } data Bar = Bar { name :: String }
getName :: Either Foo Bar -> String getName (Left f) = name f getName (Right b) = name b
However, currently you cannot: "Multiple declarations of 'name'"
Oh by the way, TDNR doesn't only work for record names, yet its use for record names is an important motivation. This was just an example. I don't want to cause any confusion while trying simplify things. -- Ozgur Akgun

I think this idea is a stairway to duck typing.
I exagerate, of course, but here is my point:
It shouldn't be difficult to make a class:
class HasName a where
name :: a -> String
The problem is when declaring Foo and Bar instances of HasName, since you
have to copy code :
data Foo = Foo String
data Bar = Bar String
instance HasName Foo where
name (Foo n) = n
instance HasName Bar where
name (Bar n) = n
I'm sure one can automatize this using TemplateHaskell, but it is not really
simple.
What I mean is that GHC should give a means to automatize this kind of
situation, for instance:
data Foo = Foo { name :: String }
(deriving HasName)
Or even:
data Foo = Foo { HasName.name }
Just an idea.
2010/11/10 Ozgur Akgun
I still don't know whether I like this idea or not, but here is the simplest definition I can think of about what it promises.
Using TDNR, it will be possible to write the following code:
data Foo = Foo { name :: String } data Bar = Bar { name :: String }
getName :: Either Foo Bar -> String getName (Left f) = name f getName (Right b) = name b
However, currently you cannot: "Multiple declarations of 'name'"
There are basically two things you can do to solve this "problem". - Use different names for your functions, a la "fooName, barName". This clutters up your code, and sometimes you may not have access to that part of the code. - Define these 2 data types in different modules and import qualified, a la "Foo.name, Bar.name". One might still think this clutters up your code.
In any case, as a programmer you need to resolve which function to use depending on types while defining 'getName'. However compiler has enough information to automate this decision for you. This is not a way to do polymorphism, this is merely a way to allow programmers define more than one function with the same name, but different types.
This kinda sounds like what java people think polymorphism is :P
-- Ozgur Akgun
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I'm totally out of my depth (coming from Java I'm probably one of these
people with a weird understanding of polymorphism (-:) probably here, but I
agree with Yves. It seems to me that if we accept that, in Ozgur's example,
name can take either a Foo or a Bar, then his getName function could also be
called name and also accept Either Foo Bar. So all of this smells strongly
of type classes. So I think Yves' idea of generating a StringName type class
or something, that all records with a field called name of type String are
automatically instances of, and adding new instances for other types
manually as need be, is good. Crazy, maybe, but good. If it quacks like a
duck and has signed the duck good behavior charter aka type class
definition, it's a duck.
JP
On Wed, Nov 10, 2010 at 1:36 PM, Yves Parès
I think this idea is a stairway to duck typing. I exagerate, of course, but here is my point:
It shouldn't be difficult to make a class: class HasName a where name :: a -> String
The problem is when declaring Foo and Bar instances of HasName, since you have to copy code : data Foo = Foo String data Bar = Bar String instance HasName Foo where name (Foo n) = n instance HasName Bar where name (Bar n) = n
I'm sure one can automatize this using TemplateHaskell, but it is not really simple.
What I mean is that GHC should give a means to automatize this kind of situation, for instance:
data Foo = Foo { name :: String } (deriving HasName)
Or even: data Foo = Foo { HasName.name }
Just an idea.
2010/11/10 Ozgur Akgun
I still don't know whether I like this idea or not, but here is the simplest definition I can think of about what it promises.
Using TDNR, it will be possible to write the following code:
data Foo = Foo { name :: String } data Bar = Bar { name :: String }
getName :: Either Foo Bar -> String getName (Left f) = name f getName (Right b) = name b
However, currently you cannot: "Multiple declarations of 'name'"
There are basically two things you can do to solve this "problem". - Use different names for your functions, a la "fooName, barName". This clutters up your code, and sometimes you may not have access to that part of the code. - Define these 2 data types in different modules and import qualified, a la "Foo.name, Bar.name". One might still think this clutters up your code.
In any case, as a programmer you need to resolve which function to use depending on types while defining 'getName'. However compiler has enough information to automate this decision for you. This is not a way to do polymorphism, this is merely a way to allow programmers define more than one function with the same name, but different types.
This kinda sounds like what java people think polymorphism is :P
-- Ozgur Akgun
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- JP Moresmau http://jpmoresmau.blogspot.com/

On 10/11/10 12:36, Yves Parès wrote:
I think this idea is a stairway to duck typing. I exagerate, of course, but here is my point:
It shouldn't be difficult to make a class: class HasName a where name :: a -> String
For accessing parts of data structures that have the same type, I agree that a type-class is best. However, this doesn't cover the situation where the type of the field is different across types, e.g. data SomeXmlDerivedThingy = C { name :: Maybe String } data Person = P { name :: String } Then you'd need a fundep on your class, which begins to get ugly: class HasName a b | a -> b where name :: a -> b It also doesn't work when the two instances of name come from totally separate libraries that don't know anything about each other (e.g. one's an xml library, the other is a database library). Then you have to add such a class in your own code to resolve the conflict. But having read the wiki page, it seems TDNR doesn't work in where I would particularly want it (e.g. record updating), so I'm not sure it's that worthwhile. As an aside, the rule on the wiki page says "Unlike normal unqualified variable occurrences, it is legal for there to be many f's in scope. To resolve which one is intended, find the type of a, and the type of all of the in-scope f's. If there is exactly one f whose type matches that of a, that resolve the occurrence of f. Otherwise the program is in error. " I wonder if special syntax is actually needed for this. How much of the language would be broken by adopting the general rule: "If the only definitions of f are at the top-level or imported, find the type of 'a' and the type of all the in-scope 'f' s. If there is exactly one match then use it, otherwise it's an error."? Thanks, Neil.

Then you'd need a fundep on your class, which begins to get ugly
It also doesn't work when the two instances of name come from totally separate libraries that don't know anything about each other (e.g. one's an xml library, the other is a database library). Then you have to add such a class in your own code to resolve the conflict. But having read the wiki page, it seems TDNR doesn't work in where I would particularly want it (e.g. record updating), so I'm not sure it's that worthwhile.
I agree with you in those cases.
But why would TDNR not work in the second case?
2010/11/10 Neil Brown
On 10/11/10 12:36, Yves Parès wrote:
I think this idea is a stairway to duck typing. I exagerate, of course, but here is my point:
It shouldn't be difficult to make a class: class HasName a where name :: a -> String
For accessing parts of data structures that have the same type, I agree that a type-class is best. However, this doesn't cover the situation where the type of the field is different across types, e.g.
data SomeXmlDerivedThingy = C { name :: Maybe String } data Person = P { name :: String }
Then you'd need a fundep on your class, which begins to get ugly:
class HasName a b | a -> b where name :: a -> b
It also doesn't work when the two instances of name come from totally separate libraries that don't know anything about each other (e.g. one's an xml library, the other is a database library). Then you have to add such a class in your own code to resolve the conflict. But having read the wiki page, it seems TDNR doesn't work in where I would particularly want it (e.g. record updating), so I'm not sure it's that worthwhile.
As an aside, the rule on the wiki page says "Unlike normal unqualified variable occurrences, it is legal for there to be many f's in scope. To resolve which one is intended, find the type of a, and the type of all of the in-scope f's. If there is exactly one f whose type matches that of a, that resolve the occurrence of f. Otherwise the program is in error. "
I wonder if special syntax is actually needed for this. How much of the language would be broken by adopting the general rule: "If the only definitions of f are at the top-level or imported, find the type of 'a' and the type of all the in-scope 'f' s. If there is exactly one match then use it, otherwise it's an error."?
Thanks,
Neil.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Neil Brown
I wonder if special syntax is actually needed for this.
+1 I think there are two issues here: 1) resolving ambiguities using types, and 2) inventing a new syntax¹ for it. It's not clear that these are at all dependent on each other.
How much of the language would be broken by adopting the general rule: "If the only definitions of f are at the top-level or imported, find the type of 'a' and the type of all the in-scope 'f' s.
My main two use cases are records (which tend to like short non-unique field names), and duplicated imports. The latter refers to the minor annoyance that I need to write import qualified Data.ByteString.Lazy.Char8 as L import Data.ByteString.Lazy.Char8 (ByteString) To be able to use unique identifiers unqualified, and still avoid collision with common prelude functions. I guess IDEs was another important argument², although one I care less for personally.
If there is exactly one match then use it, otherwise it's an error."?
It is maybe possible to do this, but I'm worried about the resulting error messages - this also needs to fail in a manner that I can understand and hopefully fix. I'm somewhat surprised that SPJ isn't commenting on this, after all he made the proposal, suggested using the dot for its syntax, and offers to implement it if there is popular support - so surely these things must have either an explicit or probable resolution. I'm just unable to find any evidence for it. (Which is what I asked for slightly upstream in the thread). -k ¹ Well, actually inventing a new meaning for an old syntax and differentiate them by clever usage of spacing. ² And maybe the reason behind the syntax? Is it easier for IDEs to look up functions for data than vice versa, or is it just more useful to the programmer? -- If I haven't seen further, it is by standing in the footprints of giants

Is it just me or does this bit in the proposal: m .lookup key .snd .reverse Which translates to this: reverse . snd . (\m -> lookup m key) $ m make no sense and refuse to type check - i.e lookup is producing a Maybe not a pair for second? I can see some benefit with TDNR for record selection as per Neil Brown's message, but I have serious doubts about the syntax and find most of the examples in proposal determinedly non-compelling.

On Wednesday 10 November 2010 1:37:41 pm Stephen Tetley wrote:
Is it just me or does this bit in the proposal:
m .lookup key .snd .reverse
Which translates to this:
reverse . snd . (\m -> lookup m key) $ m
make no sense and refuse to type check - i.e lookup is producing a Maybe not a pair for second?
I think it is intended to be parsed as follows: ((m .(lookup key)) .snd) .reverse So you get: reverse . snd . lookup key $ m The intention is, I assume, strictly to be able to resolve names like lookup on arguments other than the first. But I suppose it potentially raises questions about what all expressions are allowed to be resolved in this way. Is: m .(\m' -> lookup key m') valid? Or: m .(lookup key2 &&& lookup key2) where we resolve two overloaded functions (the same one twice, here)? The simplest answer is obviously, "no; only partially applied identifiers." -- Dan

On Nov 10, 2010, at 11:57 PM, Neil Brown wrote:
I wonder if special syntax is actually needed for this. How much of the language would be broken by adopting the general rule: "If the only definitions of f are at the top-level or imported, find the type of 'a' and the type of all the in-scope 'f' s. If there is exactly one match then use it, otherwise it's an error."?
Interesting idea. It is only after your question that I see TDNR as ad- hoc overloading and not only as simpler record notation (although it's obvious in retrospect). Such a change without new syntax seems quite radical, maybe too radical for a strongly typed language. On Nov 11, 2010, at 3:05 AM, Albert Y. C. Lai wrote:
Typed-directed name resolution brings Haskell closer to a write-only language; that is, an ambiguous phrase made total sense to the author when the author wrote it, but an independent reader will need extraordinary effort to disambiguate.
In this regard it would be closer to natural language where it is the responsibility of writers to express themselves clearly. Who writes something that requires extraordinary effort to disambiguate is an incompetent writer (or a poet, like the author of the buffalo sentence). Why blame languages instead of writers? On Nov 11, 2010, at 7:01 AM, Ryan Ingram wrote:
regular ad-hoc overloading does not make a ton of sense in Haskell; function types are complicated enough that too much ambiguity is introduced and inference becomes very difficult. But I see a lot of value in locally saying 'this particular invocation should be ad-hoc overloaded' for common functions like 'length', 'map', 'lookup', etc.
So the current proposal looks like a sensible compromise. Sebastian

On 11/11/2010, at 4:02 PM, Sebastian Fischer wrote:
Why blame languages instead of writers?
We _find fault_ with programming languages and we _blame_ their designers. A programming language is a tool. A saucepan whose handle keeps falling off is defective, and if someone who didn't realise the dangers gets a pan of boiling water over their feet, we find fault with the saucepan and blame its designer. A programming language can help in the production of working software in several ways: - making it easier to do the right thing - making it easier to find mistakes - making it harder to make mistakes - making it easier to read the result. For some tasks, C makes it very easy to do the right thing. It also makes it horribly easy to make mistakes and hard to find them. The amount of time spent maintaining a program is much higher than the amount of time spent creating it initially. That means that if you have a tradeoff between ease of writing and the other virtues of a language, ease of writing *matters* less. Consider the vexed question of repeating all or part of the record name in the field name. Yes, this *is* a burden on the person writing it. But it is a **help** to the person reading it. The same applies to using module prefixes (possibly abbreviated ones). If I see 'length' in a Haskell program, I am for sure going to think it is the one from the prelude. If I see 'B.length', I know that I need to remember what B is (probably some kind of ByteString, these days). When people enthuse about how the compiler can figure it all out, I shudder. How am *I* going to figure it all out without heavy machine assistance? If length, map, and so on had always been part of a Sequence typeclass, people would not now be talking about
a lot of value in locally saying 'this particular invocation should be ad-hoc overloaded' for common functions like 'length', 'map', 'lookup', etc.
I expected more use of type classes in the Prelude for Haskell'.

On Nov 12, 2010, at 5:43 AM, Richard O'Keefe wrote:
A saucepan whose handle keeps falling off is defective,
I do not see TDNR as unambiguously defective as a loose saucepan handle.
The amount of time spent maintaining a program is much higher than the amount of time spent creating it initially. That means that if you have a tradeoff between ease of writing and the other virtues of a language, ease of writing *matters* less.
Like you, I think that a tradeoff between readability and writability should be made in favour of readability. Unlike you, I am not convinced that TDNR trades readability for writability.
Consider the vexed question of repeating all or part of the record name in the field name. Yes, this *is* a burden on the person writing it. But it is a **help** to the person reading it. The same applies to using module prefixes (possibly abbreviated ones).
Not if the extra information is redundant. Then qualification may even impair readability by introducing unnecessary clutter. I don't think that TDNR threatens readability more than type classes already do. Not only is "Buffalo buffalo Baffalo buffalo buffalo buffalo Buffalo buffalo" a grammatically valid sentence in the English language, also `fmap fmap fmap fmap fmap fmap fmap fmap` is a type correct expression in the Haskell programming language. It can already be hard today to distinguish occurrences of overloaded functions. TDNR does not add much to this, I think. One difference is that there is a unifying type with a type class constraint for all implementations of functions with the same name when using type classes but not when using TDNR. Does this make code that is using TDNR less readable than code that is using type classes? As others have pointed out, type classes are insufficient for overloading record labels because they do not cover record updates. How can we add a special kind of overloading for record labels that also works for updates? Maybe like this: rename :: ((name :: String) @ a) => a -> a rename newName someRecord = someRecord { name = newName } This probably falls under the category of improved record systems. How difficult would it be to implement this? Can it be implemented by desugaring without substantial extensions to the type system? Sebastian

On 12/11/2010, at 6:06 PM, Sebastian Fischer wrote:
As others have pointed out, type classes are insufficient for overloading record labels because they do not cover record updates.
How can we add a special kind of overloading for record labels that also works for updates? Maybe like this:
rename :: ((name :: String) @ a) => a -> a rename newName someRecord = someRecord { name = newName }
Why is nobody talking about records in Clean? Clean is a Haskell-like language, indeed, the latest feature in Clean is an additional front-end so it can compile Haskell directly. Adapting section 5.2 from the Clean 2.1 language specification: A record type is ... an algebraic data type [with] exactly one constructor. ... a field name is attached to each of [its] arguments. Records cannot be used in a curried way. ... selection [is] by field name. When a record is created all arguments of the constructor have to be [provided] but ... in any order. ... When pattern matching ... on a record, one [need only] mention those fields one is interested in. A record can be created via a functional update [where] one [need only] specify the values for this fields that differ from the old record. RecordTypeDef = '::' TypeLhs '=' [UniversalQuantVariables] '{' (FieldName '::' [Strict] Type)-list '}' ... The semantic restrictions [of] algebraic data types also hold for record types. The field names inside one record all have to be different. It is allowed to use the same field name in different records. Record = RecordDenotation | RecordUpdate RecordDenotation = '{' [TypeName '|'] (FieldName '=' Expr)-list '}' A record can only be used if its type has been defined ... the field names must be identical to the field names ... in the corresponding type. ... The order in which the record fields are instantiated is irrelevant, but all fields have to get a value [of the right type]. ... When creating a record, its type [name] can be used to disambiguate [the type]; the type constructor can be left out if there is at least one field name [that is peculiar to the type]. There's a little gotcha there: ::T1 = {x :: Int, y :: Int} ::T2 = {y :: Int, z :: Int} ::T3 = {z :: Int, x :: Int} {x = 1, y = 2} neither x by itself nor y by itself uniquely determines a record type, so Clean 2.1 wanted {T1 | x = 1, y = 2} here. I don't happen to have a copy of the current manual handy, so I don't know if they've fixed this yet. RecordUpdate = '{' [TypeName '|'] [RecordExpr '&'] [(FieldName Selection... '=' Expr)-list] '}' Selection = '.' FieldName | '.' '[' Expr-list ']' The record written to the left of the '&' ... is the record to be updated. On the right [of] the '&' are specified the structures in which the new record differs from the old one. A structure an be any field of the record or a selection of any field or array elements of a record or array stored in this record. Notice that the functional update is not an update in the classical, destructive, sense since a new record is created. The functional update of records is performed very efficient[ly] [so] that we have not added support for destructive updates of records of unique type. The '&' operator is strict in its arguments. RecordSelection = RecordExpr ['.'TypeName] '.'FieldName Selection... | RecordExpr ['.'TypeName] '!'FieldName Selection... The "!" alternative has to do with Clean's uniqueness typing. An object of [a record] type ... can be specified as [a] pattern. Only those fields [whose] contents one would like to use [on] the right hand side need to be mentioned in the pattern. RecordPattern = '{' [TypeName '|'] (FieldName ['=' Pattern])-list '}' The type of the record must have been defined ... . The field names in the pattern must be identical to the field names [in that definition]. ... The [TypeName] can only be left out if there is at least one field name [which is not defined in any other record type]. See the T1, T2, T3 example above; I repeat that I haven't checked the latest manual and don't know if the obvious fix has been made yet. By the way, Clean can freely use '.' for selection because it uses 'o' for function composition. I remind readers once again that the latest Clean release compiles Haskell as well as Clean, so there is a sense in which records like this *are* available to some Haskell programmers. Do they meet the needs that people have been expressing here? There's no subtyping, but then, I have reasons for not using CAML. The only reason I don't use Clean is that I can't. Clean's original home was MacOS, but they moved to Windows. The latest stable release for the Mac is 32-bit only, PowerPC only, and 4 years old. Solaris has been abandoned completely. Only Windows is seeing any active support. This has nothing to do with records. Since Clean's type system is so very like the Haskell98 type system (except that their prelude breaks the numeric type classes down to the level of single operations, so that there is a + class and a * class and so on), this record system would seem to be pretty much compatible with Haskell.

On 11/11/2010 08:43 PM, Richard O'Keefe wrote:
If length, map, and so on had always been part of a Sequence typeclass, people would not now be talking about
We have a winner... It's always puzzled me that Haskell's standard containers almost completely lack any way to use them polymorphically. Maybe once people stop hating ATs it will start getting fixed...

On 12 Nov 2010, at 20:21, Andrew Coppin wrote:
On 11/11/2010 08:43 PM, Richard O'Keefe wrote:
If length, map, and so on had always been part of a Sequence typeclass, people would not now be talking about
It's always puzzled me that Haskell's standard containers almost completely lack any way to use them polymorphically.
On the contrary, there is the Edison package of containers and algorithms, since at least the late 90's, which has type classes for all of the common operations. It is high quality, and kind-of the "ideal standard" in an academic sort of way, except that almost nobody uses it. In particular, ghc did not use it internally, choosing Data.Map instead, and the legendary suspicion of programmers who refuse to use a alternative library replacing one that already comes with their compiler, means that nobody else did either. Either that, or people find it awkward to deal with the substantial extra hierarchies of type classes. Edison-API and Edison-core are available on hackage by the way. Regards, Malcolm

On 12/11/2010 08:33 PM, Malcolm Wallace wrote:
On 12 Nov 2010, at 20:21, Andrew Coppin wrote:
It's always puzzled me that Haskell's standard containers almost completely lack any way to use them polymorphically.
On the contrary, there is the Edison package
...which sounds quite interesting, except that...
except that almost nobody uses it.
I must confess, I've never actually looked at Edison (I had assumed it bit-rotted years ago), so I have no idea what it's like. I guess it's a kind of "if it was good, shouldn't everybody be using it by now?" logic.

On 12 November 2010 20:33, Malcolm Wallace
Either that, or people find it awkward to deal with the substantial extra hierarchies of type classes.
After the initial version in in PDFS it also developed operation bloat. e.g. the added Sequence class has many methods that don't fit well for standard inductive List...

On 13/11/2010, at 9:33 AM, Malcolm Wallace wrote:
On 12 Nov 2010, at 20:21, Andrew Coppin wrote:
On 11/11/2010 08:43 PM, Richard O'Keefe wrote:
If length, map, and so on had always been part of a Sequence typeclass, people would not now be talking about
It's always puzzled me that Haskell's standard containers almost completely lack any way to use them polymorphically.
On the contrary, there is the Edison package of containers and algorithms
from which the typeclass name Sequence was drawn... I have a copy of Okasaki's book. There is definitely room for a middle ground in documentation between that book and the Haddock pages for the Edison library. Something that provides an overview of what is there and why you'd use it, with examples.

It has been pointe out that languages like C, Ada, Java, and so on have type directed name resolution, or something very like it. True. But what they don't have is type variables. This means that when they see foo.bar, they know right away what the type of foo is, and will never ever get any more information about that. It can be hard enough reading Haskell as it is; at least when I see a function there's one place to look for what it is supposed to mean.

Yves Parès schrieb:
I think this idea is a stairway to duck typing. I exagerate, of course, but here is my point:
It shouldn't be difficult to make a class: class HasName a where name :: a -> String
or class Name a where name :: Accessor a String That gives you read and write access to a record. I think type class based solutions should be implemented in packages and tested in applications first, before adding another extension (exclusively) to GHC.

On 10/11/2010, at 11:56 PM, Ozgur Akgun wrote:
I still don't know whether I like this idea or not, but here is the simplest definition I can think of about what it promises.
Using TDNR, it will be possible to write the following code:
data Foo = Foo { name :: String } data Bar = Bar { name :: String }
getName :: Either Foo Bar -> String getName (Left f) = name f getName (Right b) = name b
However, currently you cannot: "Multiple declarations of 'name'"
It's not clear why this is a bad thing. If the two "name" functions MEAN the same thing (at some level of abstraction) they can/should belong to the same typeclass, in which case there is already no problem. If they don't mean the same thing, then getName has no coherent meaning. Grepping through an old release of the Erlang/OTP system, I find - approximately six thousand record declarations in - roughly one and a half million raw lines, or about one million SLOC. In Erlang, field access is <record expression> # <record name> . <field name> e.g., Event#event.trace_ts It doesn't seem to be a problem. In fact, for programming in the large it seems to be regarded more as a feature, just as always using a module prefix on imported functions is regarded as "best practice". So if being explicit is *good* for programming-in-the-large in Erlang, why is it *bad* for Haskell?

Qualification is hardly verbose, idiomatically it tends to be two characters. Qualification even with two chars is typographically ugly for infix functions. Typographically, qualification is beyond the pale for infix _type constructors_. It makes them very ugly and for many people type signatures are the most import part of source code at least for comprehension. Fortunately there aren't many uses if infix type constructors in the wild. TNDR is perhaps a marginal improvement on the first. It might be a significant improvement on the second. It doesn't appear to offer anything for the third. For my two cents, TDNR seems like a use of development effort and possibly more crucially syntax that could be spent more profitably elsewhere.

On 10/11/2010 13:52, Stephen Tetley wrote:
Qualification is hardly verbose, idiomatically it tends to be two characters.
Two characters is verbose by Haskell standards :-) Perhaps it't subjective, but if there's a click function to operate on a button, I find button.click much clearer that G.radioBtnClick button (as distinguished from M.radioBtnClick, which I imported from a different module).

I hadn't seen anyone with this particular concern, so: The page says "Using qualified names works, but it is just sufficiently inconvenient that people don't use it much", with which I disagree. Since I use qualified names, it seems like I wouldn't be able to use TDNR without compromising. So it introduces an unpleasant tension. I don't think we should introduce major features that require a certain style. I would indeed love a shorter way to get record fields, but surely there is a simpler way? I am still hoping one of the "real record system" proposals is implemented, but this would really be the nail in the coffin for them. I added my opinion to the wiki as well...

Typed-directed name resolution brings Haskell closer to a write-only language; that is, an ambiguous phrase made total sense to the author when the author wrote it, but an independent reader will need extraordinary effort to disambiguate. {-# LANGUAGE TypeDirectedNameResolution #-} import EnglishMonad import Cities(buffalo) import Animals(buffalo) import Verbs(buffalo,buffalo) {- why two buffalo's from Verbs? because they are of different types: one is present verb type and the other is past participle verb type. ever heard of Type Directed Name Resolution? -} buffalo = buffalo buffalo buffalo buffalo buffalo buffalo buffalo buffalo main = runEnglishMonad buffalo {- http://en.wikipedia.org/wiki/Buffalo_buffalo_Buffalo_buffalo_buffalo_buffalo... -}

A better solution to import-induced name clashes is Rename When Import. You can already rename the module when importing. Let's rename the imported names too. Assume I want to import this module: module SinisterlyNamedModule where data Parsec = State { stdin :: () } | Cont { runST :: (), fromList :: [()] } as State{} a b = a as Cont{} a b = b State _ <*> y = State () x <*> State _ = Cont () [] _ <*> _ = Cont () [()] on Cont{} y = y on x y@State{} = x infixr 5 <*> infixl 3 on infix 1 Cont This sinister module clashes with everything we hold dear to our hearts, left right and centre. (Yet somehow manages to avoid clashing with Prelude!) I now import it with renaming, left right and centre. The syntax import SinisterlyNamedModule( Parsec@GoodType(State@CaseOne(stdin@gfa), Cont@CaseTwo(runST@gfb, fromList@gfc) ), as@goodcase, (<*>)@foo, on@(###) ) as GoodModule renames SinisterlyNamedModule to GoodModule, Parsec to GoodType, State to CaseOne, stdin to gfa, Cont to CaseTwo, runST to gfb, fromList to gfc, as to goodcase, <*> to foo, on to ###. I use "@" instead of "as" because "as" is not a reserved word and could be an identifier, and "@" is a reserved word already. I am not sure what to do with type class names and type class method names. Perhaps allow them to be renamed too. Perhaps don't allow them to be renamed. Rather than using Type Directed Name Resolution to perpetuate dictating authoritarian names to users, let's use Rename When Import so users take back control. One name doesn't fit all. Let users choose different names to fit different uses and contexts.

On 10-11-10 02:51 PM, Albert Y. C. Lai wrote:
import SinisterlyNamedModule( Parsec@GoodType(State@CaseOne(stdin@gfa), Cont@CaseTwo(runST@gfb, fromList@gfc) ),
Sorry, that part was mistaken, and not in line with standard Haskell. Here is the correction, and more in line with standard Haskell: import SinisterlyNamedModule( Parsec@GoodType(State@CaseOne, Cont@CaseTwo, stdin@gfa, runST@gfb, fromList@gfc ), It also streamlines doing this. Assume SecondModule: module SecondModule where data Functor = Applicative { join :: String } | Category { join :: String, fix :: [Functor] } Then to import and rename: import SecondModule( Functor@Personnel(Applicative@Worker, Category@Supervisor, join@employee_name, fix@subordinates ) ) join is consistently renamed to employee_name, in particular.

In most imperative languages understanding "x.name" requires knowledge of
the type of x to understand what "name" refers to.
Now with TDNR in Haskell, "name x" requires knowledge of the type of x to
understand what "name" refers to.
As a newcomer, I think some of the coding conventions favored by
haskell-coders to be write-only, but in this case I wonder why this is
less readable in Haskell than in, say C?
Alexander
On 10 November 2010 19:05, Albert Y. C. Lai
Typed-directed name resolution brings Haskell closer to a write-only language; that is, an ambiguous phrase made total sense to the author when the author wrote it, but an independent reader will need extraordinary effort to disambiguate.
{-# LANGUAGE TypeDirectedNameResolution #-}
import EnglishMonad import Cities(buffalo) import Animals(buffalo) import Verbs(buffalo,buffalo)
{- why two buffalo's from Verbs? because they are of different types: one is present verb type and the other is past participle verb type. ever heard of Type Directed Name Resolution? -}
buffalo = buffalo buffalo buffalo buffalo buffalo buffalo buffalo buffalo
main = runEnglishMonad buffalo
{- http://en.wikipedia.org/wiki/Buffalo_buffalo_Buffalo_buffalo_buffalo_buffalo_Buffalo_buffalo-}
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Nov 10, 2010 at 11:59:28AM +0200, John Smith wrote:
http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio...
The problem with this is that it conflates two orthogonal features: type-directed name resolution proper (also known as ad hoc overloading), and a fancy postfix application syntax. There is no connection between these except that both are useful for accessing records in a particular way. So the proposal seems to be tailored specifically to fix some inconveniences with records. I'd much rather see a true record system for Haskell, since that would fix the namespace conflict problem in a more robust way. Plain ad hoc overloading might or might not be a sensible addition to Haskell, but please at least drop the "x .f" syntax, it's a pointless hack that makes the lexical status of "." even more difficult than it currently is. After all, one can simply define e.g. "x .$ f = f x" if postfix application is needed. Cheers, Lauri

On Wednesday 10 November 2010 2:08:56 pm Lauri Alanko wrote:
So the proposal seems to be tailored specifically to fix some inconveniences with records. I'd much rather see a true record system for Haskell, since that would fix the namespace conflict problem in a more robust way.
I certainly agree with this.
Plain ad hoc overloading might or might not be a sensible addition to Haskell, but please at least drop the "x .f" syntax, it's a pointless hack that makes the lexical status of "." even more difficult than it currently is. After all, one can simply define e.g. "x .$ f = f x" if postfix application is needed.
However, I don't completely agree with this. I agree with '.' perhaps not being a good choice. However, if we do add completely ad-hoc overloading, I think it might be useful to give functions subject to it a different syntactic appearance, to alert to where it is being used. ---------- For a case study, Agda has type directed name resolution, but *only* for constructors. If you try to define something else with the same name as a constructor, or define two other values with the same name, it will reject your program. This can be useful, since you can write: _+N_ : Nat -> Nat -> Nat zero +N n = n suc m +N n = suc (m +N n) _+F_ : forall {i j} -> Fin i -> Fin j -> Fin (i +N j) zero +F n = n suc m +F n = suc (m +F n) But, it has two caveats, I think: 1) It seems significantly less of a burden due to the fact that Agda requires you to write signatures for *every* function you write already. 2) Even with just the constructor case, enough ambiguity is introduced that the Agda implementors recently added the ability to qualify a constructor by its associated datatype. For instance, the signature: foo : forall n -> n /= suc n is ambiguous, since n has no principal type. You could fix this via: foo : forall (n : Nat) -> n /= suc n but there is now also support to write: foo : forall n -> n /= Nat.suc n I'll admit, the Agda overloading is handy. But I've always considered Haskell's lack of ad-hoc overloading to be a feature. Type classes give sensible types for what would normally be ad-hoc. Adding back ad-hoc functions that have no available general type feels like a step backward. Perhaps that's just me, though. -- Dan

On 11/10/10 4:59 PM, Dan Doel wrote:
I'll admit, the Agda overloading is handy. But I've always considered Haskell's lack of ad-hoc overloading to be a feature. Type classes give sensible types for what would normally be ad-hoc. Adding back ad-hoc functions that have no available general type feels like a step backward. Perhaps that's just me, though.
It's not just you. I'd rather see a complete rewrite of the record system in order to make it into a real record system (perhaps by partly unifying records and modules, a la Agda and many other dependently typed languages). And I think TDNR is an abomination that merely paints over the problem; it doesn't solve the actual issue, and it only makes it harder to implement a solution later. -- Live well, ~wren

On Wed, Nov 10, 2010 at 11:08 AM, Lauri Alanko
Plain ad hoc overloading might or might not be a sensible addition to Haskell, but please at least drop the "x .f" syntax, it's a pointless hack that makes the lexical status of "." even more difficult than it currently is. After all, one can simply define e.g. "x .$ f = f x" if postfix application is needed.
Do you have a better suggestion? The arguments for . & postfix application: - Standard practice in other languages - feels similar to qualified names - postfix application is really useful for IDEs Arguments against: - . is used for too much stuff already - postfix application isn't really Haskelly I personally think that the arguments in favor are pretty strong. As you've mentioned, regular ad-hoc overloading does not make a ton of sense in Haskell; function types are complicated enough that too much ambiguity is introduced and inference becomes very difficult. But I see a lot of value in locally saying 'this particular invocation should be ad-hoc overloaded' for common functions like 'length', 'map', 'lookup', etc. -- ryan

On 10/11/2010, at 10:59 PM, John Smith wrote:
Obvious benefits of this are that conflicting function names from imported modules can be used without qualification (verbose)
Why is making life harder for people reading the code counted as a "benefit"? Let me offer an example from another language. aStream next => consume an item from an input stream and return it aDate next => same as (aDate addDays: 1). How do I cope in Smalltalk? Simple: you don't put the type name in the *function*, you put the type name in the *variable*. If the code says frobnitz next I haven't the least clue what it does or where to look to find out.
it is often desirable to have the same field names for many records in the same module.
I'm not sure that it is desirable to have "many records in the same module" in the first place.

"Richard O'Keefe"
it is often desirable to have the same field names for many records in the same module.
I'm not sure that it is desirable to have "many records in the same module" in the first place.
One possibility might be to allow mulitple module definitions in the same file, making it easier to wrap each record in its own module without running into a Java-like forest of files. (I've proposed this before, and although I don't remember the specifics, ISTR the response being mostly negative.) -k -- If I haven't seen further, it is by standing in the footprints of giants

On 11/11/2010 5:21 PM, Ketil Malde wrote:
"Richard O'Keefe"
writes: it is often desirable to have the same field names for many records in the same module.
very much so, this is currently possible, with the restriction that the field names must have the same type modulo the record it is selecting on. what is disirable is that this restriction be lifted.
I'm not sure that it is desirable to have "many records in the same module" in the first place.
this should really be a choice of the programmer.
One possibility might be to allow mulitple module definitions in the same file, making it easier to wrap each record in its own module without running into a Java-like forest of files.
a module represents a compilation unit which happens to be a file, in haskell it also represents a name space and a means for control of that namespace. Compilation units and name space management are orthoganal issues although obviously connected. SML for example manages the name space with Functors and does not explicitly name the compilation units, haskell names the compilation units i.e. modules, but I have had some thoughts along the same lines, myself, more on this later .. discussion of the haskell record system and syntax has a long history, just a quick search ... http://www.mail-archive.com/haskell@haskell.org/msg17725.html http://www.haskell.org/pipermail/haskell-prime/2006-March/000836.html http://www.mail-archive.com/haskell@haskell.org/msg13394.html http://www.mail-archive.com/haskell@haskell.org/msg20516.html in 2003 http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html I quote "Haskell lacks a serious record system. (The existing mechanism for named fields in data types was always seen as a stop-gap measure.) At the 1999 Haskell Workshop, Mark Jones and Simon Peyton Jones proposed a more fully-fledged record system, closely modelled on the TRex system implemented in Hugs. But Simon never got around to implementing it in GHC. Why not? Mainly because the implementation cost turned out to be relatively high." .. in the intervening years we have GADTS, type families, associated types tec ... but with respect to records what has changed ? In my mind, the feature that I most wish for, and what haskell lacks is the ability to manage the module name space with respect to record label names. Yes, I often want to define a record with the same label name at a different type. many languages have a construct "with <record>" which "unqualifies" the names introduced by the record definition, those names being implicitly qualified when defined. Haskell label names are implicitly "unqualified". I have often thought that a minimal extension to Haskell compatible with the current record system that could ameliorate the situation would be data Foo = Foo { label1 :: Int, label2 :: String } qualified where such a qualified data declaration would hide labels label1 and label2, making the available only as Foo.label1, Foo.label2., etc where we have a qualified record we should be able to "unqualify" it as import data Foo or rename it import data Foo qualified as Bar which would introduces Bar.label1, Bar.label2 etc. None of the above is incompatible with the current record system and introduces no new keywords. This proposal solely addresses the issue of name space management.
(I've proposed this before, and although I don't remember the specifics, ISTR the response being mostly negative.)
-k

On Thu, Nov 11, 2010 at 1:34 AM, John Lask
On 11/11/2010 5:21 PM, Ketil Malde wrote:
"Richard O'Keefe"
writes: it is often desirable to have the same field names for many records in the same module.
very much so, this is currently possible, with the restriction that the field names must have the same type modulo the record it is selecting on.
what is disirable is that this restriction be lifted.
Haskell has a wonderful history of being careful to consider both sides of a restriction. One one hand, a restriction can make it harder to write something you want to write. On the other hand, a restriction can provide properties that make it easy to transform and reason about your program. So I am not ready to accept your claim that this is desirable without further justification.

On Thu, Nov 11, 2010 at 1:41 AM, Luke Palmer
On Thu, Nov 11, 2010 at 1:34 AM, John Lask
wrote: On 11/11/2010 5:21 PM, Ketil Malde wrote:
"Richard O'Keefe"
writes: it is often desirable to have the same field names for many records in the same module.
very much so, this is currently possible, with the restriction that the field names must have the same type modulo the record it is selecting on.
what is disirable is that this restriction be lifted.
Haskell has a wonderful history of being careful to consider both sides of a restriction. One one hand, a restriction can make it harder to write something you want to write. On the other hand, a restriction can provide properties that make it easy to transform and reason about your program.
So I am not ready to accept your claim that this is desirable without further justification.
Sorry for the self-reply. I just want to clarify, I didn't mean to write off your well-thought-out message with this simple comment. I was just drawing attention to the duality of restrictions. Luke

On Thu, Nov 11, 2010 at 07:04:16PM +1030, John Lask wrote:
it is often desirable to have the same field names for many records in the same module.
very much so, this is currently possible, with the restriction that the field names must have the same type modulo the record it is selecting on.
what is disirable is that this restriction be lifted.
Why on earth? I thought that the motivation for this feature was simply to deal with naming conflicts with _unrelated_ records from _unrelated_ modules without having to resort to qualified names. But I can't see why someone would use the same accessor name for unrelated records in a single module. And if the records are related (and the field is conceptually "the same" for the records), then you can use a type class to overload the accessor name in a controlled fashion. So why would you ever need to reuse the same field name in the same module? Lauri

On Thu, Nov 11, 2010 at 2:24 PM, Lauri Alanko
On Thu, Nov 11, 2010 at 07:04:16PM +1030, John Lask wrote:
it is often desirable to have the same field names for many records in the same module.
very much so, this is currently possible, with the restriction that the field names must have the same type modulo the record it is selecting on.
what is disirable is that this restriction be lifted.
Why on earth? I thought that the motivation for this feature was simply to deal with naming conflicts with _unrelated_ records from _unrelated_ modules without having to resort to qualified names. But I can't see why someone would use the same accessor name for unrelated records in a single module. And if the records are related (and the field is conceptually "the same" for the records), then you can use a type class to overload the accessor name in a controlled fashion.
So why would you ever need to reuse the same field name in the same module?
data PetOwner data FurnitureOwner data Cat = Cat { owner :: PetOwner } data Chair = Chair { owner :: FurnitureOwner } Just the first thing that came to mind, this kind of thing comes up often enough to be an irritant. I'm not sure whether or not TDNR is a good solution to the problem, just pointing out a use case. Micahel

On Thu, Nov 11, 2010 at 03:17:39PM +0200, Michael Snoyman wrote:
data PetOwner data FurnitureOwner
data Cat = Cat { owner :: PetOwner } data Chair = Chair { owner :: FurnitureOwner }
These are clearly related uses, so as I said, you can use a type class to overload the accessor name in a controlled fashion. {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-} data PetOwner data FurnitureOwner data Cat = Cat { catOwner :: PetOwner } data Chair = Chair { chairOwner :: FurnitureOwner } class Owned a b | a -> b where owner :: a -> b instance Owned Cat PetOwner where owner = catOwner instance Owned Chair FurnitureOwner where owner = chairOwner (You can also use associated type families for the same effect.) Lauri

On Thu, Nov 11, 2010 at 3:10 PM, Lauri Alanko
On Thu, Nov 11, 2010 at 03:17:39PM +0200, Michael Snoyman wrote:
data PetOwner data FurnitureOwner
data Cat = Cat { owner :: PetOwner } data Chair = Chair { owner :: FurnitureOwner }
These are clearly related uses, so as I said, you can use a type class to overload the accessor name in a controlled fashion.
{-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}
data PetOwner data FurnitureOwner
data Cat = Cat { catOwner :: PetOwner } data Chair = Chair { chairOwner :: FurnitureOwner }
class Owned a b | a -> b where owner :: a -> b
instance Owned Cat PetOwner where owner = catOwner
instance Owned Chair FurnitureOwner where owner = chairOwner
(You can also use associated type families for the same effect.)
Well, it's not exactly the same. For example: myCat = Cat { owner = michael } versus myCat = Cat { catOwner = michael } Not to mention that with TDNR, there is much less typing involved: no need to declare a type class, declare instances, export the type class. Michael

On 11 November 2010 13:10, Lauri Alanko
{-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}
data PetOwner data FurnitureOwner
data Cat = Cat { catOwner :: PetOwner } data Chair = Chair { chairOwner :: FurnitureOwner }
class Owned a b | a -> b where owner :: a -> b
instance Owned Cat PetOwner where owner = catOwner
instance Owned Chair FurnitureOwner where owner = chairOwner
This is fairly onerous for people who are programming to an outside schema (i.e. a relational database) as it leads to boiler plate along two axes - data type definitions plus class definitions for accessors. I don't like the details current TDNR proposal, but if improved records are never going to happen, TDNR has benefit for this situation. Incidentally there is now a member of the ML family with a sophisticated record system - MLPolyR: http://ttic.uchicago.edu/~wchae/wiki/pmwiki.php

11.11.2010 16:53, Stephen Tetley пишет:
On 11 November 2010 13:10, Lauri Alanko
wrote: {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}
data PetOwner data FurnitureOwner
data Cat = Cat { catOwner :: PetOwner } data Chair = Chair { chairOwner :: FurnitureOwner }
class Owned a b | a -> b where owner :: a -> b
instance Owned Cat PetOwner where owner = catOwner
instance Owned Chair FurnitureOwner where owner = chairOwner
This is fairly onerous for people who are programming to an outside schema (i.e. a relational database) as it leads to boiler plate along two axes - data type definitions plus class definitions for accessors.
I don't like the details current TDNR proposal, but if improved records are never going to happen, TDNR has benefit for this situation.
That's kinda the point, it can work the other way: ugly solution like TDNR can prevent improved records from ever appearing.
Incidentally there is now a member of the ML family with a sophisticated record system - MLPolyR: http://ttic.uchicago.edu/~wchae/wiki/pmwiki.php _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Nov 11, 2010 at 2:59 PM, Miguel Mitrofanov
11.11.2010 16:53, Stephen Tetley пишет:
On 11 November 2010 13:10, Lauri Alanko
wrote: {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}
data PetOwner data FurnitureOwner
data Cat = Cat { catOwner :: PetOwner } data Chair = Chair { chairOwner :: FurnitureOwner }
class Owned a b | a -> b where owner :: a -> b
instance Owned Cat PetOwner where owner = catOwner
instance Owned Chair FurnitureOwner where owner = chairOwner
This is fairly onerous for people who are programming to an outside schema (i.e. a relational database) as it leads to boiler plate along two axes - data type definitions plus class definitions for accessors.
I don't like the details current TDNR proposal, but if improved records are never going to happen, TDNR has benefit for this situation.
That's kinda the point, it can work the other way: ugly solution like TDNR can prevent improved records from ever appearing.
I tend to be mistrustful of this kind of perfect-is-the-enemy-of-the-good thinking, it rarely ends up working out well. Usually the result is that you end up with nothing. And while you can't prove a counterfactual, I'm really not sure if getting the 'good' ever actually acts to hold back the 'perfect' later. The mechanism is intuitive enough: people decide the 'good' solution is good enough, resulting in less demand for the better one. But to take the present situation at least, there is plenty of demand for an improved records system and it doesn't seem to be getting us any closer to gaining one. Maybe implementing TDNR will make people complacent and delay it further, maybe it'll actually make people hungrier for further improvement, maybe it'll have no effect, who knows? The point is that refusing something you can have now (though of course it's an open question whether TDNR is something we can "have now") out of fear that it'll prevent you getting something better later is speculative and often backfires.
Incidentally there is now a member of the ML family with a sophisticated record system - MLPolyR: http://ttic.uchicago.edu/~wchae/wiki/pmwiki.php _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.

The point is that refusing something you can have now (though of course it's an open question whether TDNR is something we can "have now") out of fear that it'll prevent you getting something better later is speculative and often backfires.
I think we are very far from having TDNR "now". It is really quite complicated to interleave name resolution with type checking in any compiler. So far, we have a design, that's all, no implementation. We also have (several) designs for proper record systems. If the outcome of this discussion is a clamour for better records instead of TDNR, then that would certainly make me happy. Regards, Malcolm

If the outcome of this discussion is a clamour for better records instead of TDNR, then that would certainly make me happy.
Regards, Malcolm
well I certainly am clamouring for better records. This motivated my original reply this post. The trouble is, what constitutes better records? There are as many views as users of Haskell, I bet. My main motivation is: As mentioned in my original post: better name space management. Surprisingly enough, I find the current record system is quite usable, bar one feature. My particular use case: commercial applications make heavy use of records (in connection with relational databases) and name clashes are inevitable. As I tried to point out in my original post, issues of name space management are orthogonal to the type system, but obviously related as the type system in Haskell is used to distinguish names. The thrust of discussion and work on the record system, in so far as Haskell has been concerned, has been at the type system level, an necessarily so: work on representing the "has a" relation, extensibility etc at the type level. Some relatively usable libraries have been developed that provide this support (eg HList). none of this can address my particular issue: name space management, that is, managing the scope of record labels. The type system is not the solution to all problems. Hence my proposal. I don't envisage that my issue will be addressed anytime soon, if at all. But by raising it I hope to broaden the focus of the discussion. The trouble with any rework of the current record system: which way to take it ... the design space is large what would users want ... - light weight records (c.f. ML) - first class labels (accessors and setters) - extensible records - sub-typing or in my case - better name space management perhaps given the many avenues for exploration of type system support for record systems, we could make use of existing libraries with rebind-able syntax?? again quoting http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html "Haskell lacks a serious record system. (The existing mechanism for named fields in data types was always seen as a stop-gap measure.)" isn't it about time this changed?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This motivated my original reply this post. The trouble is, what constitutes better records? There are as many views as users of Haskell, I bet.
My main motivation is:
As mentioned in my original post: better name space management.
Surprisingly enough, I find the current record system is quite usable, bar one feature. My particular use case: commercial applications make heavy use of records (in connection with relational databases) and name clashes are inevitable.
I too would like better records, and I too find them usable if not ideal in their current form. They wind up being doubly qualified, e.g. 'State.state_blocks st' and can be quite verbose. Consider an extreme case: set_track_width view_id width = do track_views <- modify_at "set_track_width" (Block.view_tracks view) tracknum $ \tview -> tview { Block.track_view_width = width } update_view view_id (view { Block.view_tracks = track_views }) update_view view_id view = modify $ \st -> st { state_views = Map.adjust (const view) view_id (state_views st) } What I am actually *doing* here, is: state.get_view(view_id).tracks[tracknum].width := width Part of the difference is that updating data is fundamentally more idiomatic in an imperative language, and it's true this is a rare example (modify_at updates a list at an index, ignore that :P). But the fact is that the difference between what I write and what I mean is reaching almost comical java-like levels. 'modify $ \st -> st { State.state_x = f (State.state_x st) }' is quite common, and modifying two levels deep also happens (which requires an auxiliary function to be readable). And the 'f' is buried in the middle of a bunch of boilerplate.
- light weight records (c.f. ML)
I actually don't feel a lot of need for this... if I want a short-lived data structure I just use a tuple. I use records when they are being passed through multiple functions, and at that point I'm probably going to at least a type synonym, and then we're back to heavy-weight, right? The only place I can think of where light-weight records would be handy is simulating keyword args... but even then it seems hardly a burden to declare a datatype for it, and it gives you a place to put documentation. Any other uses out there?
- first class labels (accessors and setters)
I would love this. I don't even think accessors is really the problem, they compose nicely as just functions even if they are a little wordy. It's update that's the killer. The reason I say it's bearable even though it can be quite verbose is that update (at least in my programs) is uncommon enough that I can factor all common updates into functions and then just call those.
- extensible records - sub-typing
Unlike the above things which make it more convenient to write the same code, it sounds like these things would actually let you write new kinds of code. However, I don't really feel like I'm missing that. Maybe it's a "blub" problem? Are there some examples of cool things you could do with either of the above that you can't do (conveniently) without? In fact, given that updates seem to be the only thing I care about, maybe I'd be made almost as happy by a functional refs library. There are several competing implementations on hackage but AFAIK none are considered universal and standard (none are in HP, for instance).
http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html
"Haskell lacks a serious record system. (The existing mechanism for named fields in data types was always seen as a stop-gap measure.)"
isn't it about time this changed?
I sure think so :)

On 11/11/2010 11:48 PM, John Lask wrote:
again quoting
http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html
"Haskell lacks a serious record system. (The existing mechanism for named fields in data types was always seen as a stop-gap measure.)"
isn't it about time this changed?
Records do leave quite a bit to be desired. But does anybody actually have a concrete alternative proposal yet? Personally I'm not really keen on TDNR; I'd prefer records that aren't so inconvenient. But I have no idea how to design that.

Records do leave quite a bit to be desired. But does anybody actually have a concrete alternative proposal yet?
A few months ago I proposed a couple of extensions [1] on -cafe. The jist of it is in the following:
someUpdate :: MyRecord -> MyRecord someUpdate myRecord = myRecord { field1 = f $ field1 myRecord , field2 = g $ field2 myRecord , field3 = h $ filed3 myRecord }
becomes
someUpdate :: MyRecord -> MyRecord someUpdate = \{field1 => f, field2 => g, field3 => h}
The two syntax changes here are: 1. '=' remains as assignment in record updates, but => is added and means 'field is transformed by', and 2. "\{...}" is a first-class "lambda update". It's made possible by the 1 since with 1 you no longer need to reference the entire record anywhere in the update Consider what this would do for nested updates:
UpdateTripleInner :: (Inner->Inner) -> MyTriplyNestedRecord -> MyTriplyNestedRecord UpdateTripleInner f = \{inner1 => \{inner2 => \{inner3 => f }}}
I cringe to imagine what the equivalent is in current Haskell syntax.
Anyone want to try it? Not me!
These extensions, admittedly, don't do anything for the namespacing
problem, which might be a bigger issue than awkward updates. I submit
that it's a different and somewhat unrelated issue, though I'd love to
see something that addresses both (all?) of the issues!
--Jonathan Geddes
[1] http://www.mail-archive.com/haskell-cafe@haskell.org/msg81509.html
On Fri, Nov 12, 2010 at 1:29 PM, Andrew Coppin
On 11/11/2010 11:48 PM, John Lask wrote:
again quoting
http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html
"Haskell lacks a serious record system. (The existing mechanism for named fields in data types was always seen as a stop-gap measure.)"
isn't it about time this changed?
Records do leave quite a bit to be desired. But does anybody actually have a concrete alternative proposal yet?
Personally I'm not really keen on TDNR; I'd prefer records that aren't so inconvenient. But I have no idea how to design that.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 12 November 2010 21:48, Jonathan Geddes
I cringe to imagine what the equivalent is in current Haskell syntax. Anyone want to try it? Not me!
Perhaps not pretty - but it is regular and avoids Template Haskell an manages for the few times I have records-in-records: doubleInner3OfA :: A -> A doubleInner3OfA = (\s a -> s { inner1 = f1 a }) <*> inner1 where f1 = (\s a -> s { inner2 = f2 a }) <*> inner2 f2 = (\s a -> s { inner3 = 2 * a }) <*> inner3 data A = A { inner1 :: B } deriving (Eq,Show) data B = B { inner2 :: C } deriving (Eq,Show) data C = C { inner3 :: Int } deriving (Eq,Show) t1 = A (B (C 1)) demo1 = doubleInner3OfA $ t1

On Fri, Nov 12, 2010 at 22:48, Jonathan Geddes
Records do leave quite a bit to be desired. But does anybody actually have a concrete alternative proposal yet?
A few months ago I proposed a couple of extensions [1] on -cafe.
[snip]
Consider what this would do for nested updates:
UpdateTripleInner :: (Inner->Inner) -> MyTriplyNestedRecord -> MyTriplyNestedRecord UpdateTripleInner f = \{inner1 => \{inner2 => \{inner3 => f }}}
I cringe to imagine what the equivalent is in current Haskell syntax. Anyone want to try it? Not me!
You can do this very conveniently already using the fclabels package: updateTrippleInner = modL (inner3 . inner2 . inner1) Here, inner1/2/3 are not record fields, but Lenses. You have to construct the lenses themselves, but this is very easy, and can be automated using Template Haskell. Other packages like data-accessor have similar functionality. Erik

On 12/11/2010, at 2:26 AM, Malcolm Wallace wrote:
The point is that refusing something you can have now (though of course it's an open question whether TDNR is something we can "have now") out of fear that it'll prevent you getting something better later is speculative and often backfires.
I think we are very far from having TDNR "now". It is really quite complicated to interleave name resolution with type checking in any compiler. So far, we have a design, that's all, no implementation. We also have (several) designs for proper record systems.
Disciple has TDNR, and there is an implementation in DDC. It is a bit complicated, mainly because you can't determine the call graph of the program before starting inference. In ML style inference you're supposed to let-generalise groups of recursive bindings together, but for TDNR you can only determine what is recursive once you've resolved the names (which depends on the types, which you need to infer). The algorithm is described starting at page 168 in my thesis here: http://www.cse.unsw.edu.au/~benl/papers/thesis/lippmeier-impure-world.pdf Disciple doesn't have type functions or associated types though. I think it'd be "nicer" for GHC if we could leverage some of the other extensions, as suggested in Mark Lentczner's post. Ben.

but if improved records are never going to happen
Just to inject the usual comment: improved records have been here for quite some time now. In Hugs, there is TREX; in GHC, you can define your own. No need to wait for them. Using one particular random variation of extensible records and labels: {-# LANGUAGE CPP,TypeOperators,QuasiQuotes #-} import Data.Label import Data.Record data PetOwner = PetOwner deriving Show data FurnitureOwner = FurnitureOwner deriving Show -- abstract out labels so that we can bridge backwards-incompatibility -- http://haskell.org/haskellwiki/Upgrading_packages/Updating_to_GHC_7 #if __GLASGOW_HASKELL__>=700 catOwner = [l|catOwner|] chairOwner = [l|chairOwner|] owner = [l|owner|] #else catOwner = [$l|catOwner|] chairOwner = [$l|chairOwner|] owner = [$l|owner|] #endif -- we can still give unique labels, if we want oldcat = catOwner := PetOwner :# () oldchair = chairOwner := FurnitureOwner :# () -- but we don't have to, even if the field types differ newcat = owner := PetOwner :# () newchair = owner := FurnitureOwner :# () main = do print $ oldcat #? catOwner print $ oldchair #? chairOwner print $ newcat #? owner print $ newchair #? owner This variation collected some of the techniques in a sort-of library, which you can find at http://community.haskell.org/~claus/ in files (near bottom of page) Data.Record Data.Label Data.Label.TH (there are examples in Data.Record and labels.hs) That "library" code was for discussion purposes only, there is no cabal package, I don't maintain it (I just had to update the code for current GHC versions because of the usual non-backward-compatibility issues, and the operator precedences don't look quite right). There are maintained alternatives on hackage (eg, HList), but most of the time people define their own variant when needed (the basics take less than a page, see labels.hs for an example). I'm not aware of any systematic performance studies of such library-defined extensible records (heavy use of type-class machinery that could be compile-time, but probably is partly runtime with current compilers; the difference could affect whether field access is constant or not). It is also worrying that these libraries tend to be defined in the gap between Hugs' strict (only allow what is known to be sound) and GHC's lenient (allow what doesn't bite now) view of type system feature interactions. The practical success weighs heavily in favour of GHC's approach, but I'm looking forward to when the current give-it-a-solid-basis-and-reimplement-everything effort in GHC reaches the same level of expressiveness as the old-style lenient implementation!-) Claus

On 12/11/2010, at 2:53 AM, Stephen Tetley wrote:
This is fairly onerous for people who are programming to an outside schema (i.e. a relational database) as it leads to boiler plate along two axes - data type definitions plus class definitions for accessors.
Boiler plate is GOOD news, because the generation of boiler plate can be automated.
Incidentally there is now a member of the ML family with a sophisticated record system - MLPolyR: http://ttic.uchicago.edu/~wchae/wiki/pmwiki.php
There is or was also SML# (not related to .Net).

On 12/11/2010, at 2:17 AM, Michael Snoyman wrote:
So why would you ever need to reuse the same field name in the same module?
data PetOwner data FurnitureOwner
data Cat = Cat { owner :: PetOwner } data Chair = Chair { owner :: FurnitureOwner }
Just the first thing that came to mind, this kind of thing comes up often enough to be an irritant. I'm not sure whether or not TDNR is a good solution to the problem, just pointing out a use case.
I'm afraid it's not a *convincing* use case. It's not convincing because here "owner" *means different things*. The genius of typeclasses was that it gave us a way to implement functions differently for different types while still referring all the implementations to a single interface, so that they should all in _some_ sense mean the same thing. If x owns a pet, then x is responsible for providing it with food, water, shelter, and medical treatment, and can be gaoled for failing to do so. If y owns a chair, then y can sit on it, spray it with mayonnaise, smash it to pieces, burn it to ashes, or do pretty much anything y pleases. There is no duty to provide a pet chair with food, water, &c. There was a German case a couple of years ago where a man described a fantasy of his on the internet and asked for a volunteer to help him carry it out in reality. He got one. The other man came to his flat, they had sex, and then the first man killed the other and ate him. My take on this was that there were things you *can't* consent to. The colleague I discussed it with a couple of days ago said "If I don't own my body, I own nothing" and said that owning your own body had to mean having the right to volunteer to killed and eaten. He's such a nice man, my colleague, and deeply skilled in logic. Thinking about this, I came to the conclusion that when he and I say "my body" we mean different things. I mean INalienable possession, he means alienable possession. It's like the difference between a dog's meat (food for the dog from another animal, take it away and the dog is hungry) and a dog's flesh (the dog's own matter, take it away and there is no dog). There's that rather silly piece in Plato's Republic where he says "Both the community of property and the community of families ... tend to make them more truly guardians; they will not tear the city in pieces by differing about "mine" and "not mine"; ... but all will be affected as far as may be by the same pleasures and pains ..." Since when can my hunger be the same as your hunger? Since when can my bladder discomfort (I've been sitting at this keyboard too long) be the same as yours? Since when can your pleasure in eating onions be the same as mine (I _hate_ onions, and even if I didn't, I wouldn't want to eat the _same_ bits of onion you're eating). Greek didn't distinguish between alienable and inalienable possession. If that kind of ambiguity can lead the most famous philospher in history to write twaddle, what is confusion in our function names going to do to Haskell programmers? TDNR has the same attractiveness as a sugar coated laxative tablet, and I expect the end product of both to be the same.

On 12/11/2010 9:22 AM, Richard O'Keefe wrote:
On 12/11/2010, at 2:17 AM, Michael Snoyman wrote:
So why would you ever need to reuse the same field name in the same module?
data PetOwner data FurnitureOwner
data Cat = Cat { owner :: PetOwner } data Chair = Chair { owner :: FurnitureOwner }
Just the first thing that came to mind, this kind of thing comes up often enough to be an irritant. I'm not sure whether or not TDNR is a good solution to the problem, just pointing out a use case.
I'm afraid it's not a *convincing* use case. It's not convincing because here "owner" *means different things*.
consider "length" ... I have records with the attribute length, length can be given as an Int, Double, Float or maybe as a constructed type "Length", length's use as a record selector would also clash with List.length. All these have the same denotation. should I then seporate into int_length, float_length, or use rec1_length, rec2_length etc etc... for proper name space management why should I have to define each record that defines a length field with different representation in distinct modules, or with different names for the field label when they denote the same thing? This is easily handled in C, Pascal, PL/1, Cobol why not in Haskell ?

On Thu, Nov 11, 2010 at 8:16 PM, John Lask
consider "length" ...
I have records with the attribute length, length can be given as an Int, Double, Float or maybe as a constructed type "Length", length's use as a record selector would also clash with List.length. All these have the same denotation.
should I then seporate into int_length, float_length, or use rec1_length, rec2_length etc etc...
class Lengthy a where type LengthType a length :: a -> LengthType a This extends easily to lenses if you want setters.
This is easily handled in C, Pascal, PL/1, Cobol why not in Haskell ?
By this argument, Haskell should provide global mutable state and
allow side-effects universally.
--
Dave Menendez

My tuppence: I feel like the main impetus for TDNR is the awkwardness of records, especially when there are multiple record types within a module (as there often are). Now, if one proceeds as one has to today, then one may find: data Foo = Foo { fooName :: String, fooValue :: Double } data Bar = Bar { barName :: String, barValue :: [String], barSubbars :: [Bar] } Let us, for sake of argument, ignore that perhaps fooName and barName represent the same semantic concept and these should all somehow be refactored. I suspect that the prime annoyance, the thing that makes us yearn for our old C/C++/Java/Python ways, is the tediousness of having to prefix all the field names with "foo" or "bar". Especially when the data type name is large, one ends up having to invent coding conventions one doesn't want to: data ExecutionTraceSummary = ExecutionTraceSummary { etsStart :: Time; ... } So imagine that we take the tedium out of typing all those prefixes by anointing some initial character, say the apostrophe, as a sort of name mangler: data Foo = Foo { 'name :: String, 'value :: Double } data Bar = Bar { 'name :: String, 'value :: [String], 'subbars :: [bar] } data ExecutionTraceSummary = ExecutionTraceSummary { 'start :: Time, ... } Now, to use them, perhaps we have to explicitly write the full form: showFoo :: Foo -> String showFoo f = Foo'name f ++ "(" ++ show (Foo'value f) ++ ")" We could allow a form of shortened local reference by allowing the full form to "flow through" type declarations: type ETS = ExecutionTraceSummary logExecutionTraceSummary :: ExecutionTraceSummary -> IO () logExecutionTraceSummary s = do putStr $ ETS'start s Mind you, I realize that apostrophe may not work here, and details haven't been worked out. [...that was the first pence, here comes the second...] If you buy any of that, then one could allow, in the manner pointed out by some (though in particular I'm thinking of David Menendez's example), that this construction could imply a type class and associated type. That is, the first appearance of 'name in a record implies this: class <C>'name a where type <R>'name a :: * 'name :: a -> <R>'name a and for each appearance of 'name :: X as a field of Foo: instance <C>'name Foo where type <R>'name Foo = X 'name = Foo'name (Here, <C> and <R> are some unwritable prefixes used by the compiler. It remains to be seen if these should be module scoped or program global.) So, in the case (repeated from above): data Foo = Foo { 'name :: String, 'value :: Double } data Bar = Bar { 'name :: String, 'value :: [String], 'subbars :: [Bar] } We get auto generated: class <C>'name a where type <R>'name a :: * 'name :: a -> <R>'name a class <C>'value a where type <R>'value a :: * 'value :: a -> <R>'value a class <C>'subbars a where type <R>'subbars a :: * 'subbars :: a -> <R>'subbars a instance <C>'name Foo where type <R>'name Foo = String 'name = Foo'name instance <C>'name Bar where type <R>'name Bar = String 'name = Bar'name instance <C>'value Foo where type <R>'value Foo = Double 'value = Foo'value instance <C>'value Bar where type <R>'value Bar = [String] 'value = Bar'value instance <C>'subbars Bar where type <R>'subbars Bar = [Bar] 'subbars = Bar'subbars *Now* one can write: showFoo :: Foo -> String showFoo f = 'name f ++ "(" ++ show ('value f) ++ ")" nameBoth :: Foo -> Bar -> String nameBoth f b = 'name f ++ " " ++ 'name b None of this requires any more type machinery than already exists with TypeFamilies. It perhaps suffer some of the prior objections to implying semantic equivalence (in say the 'value fields) where none exists. But, it is limited in scope to fields, and only when one uses the special naming sigil (apostrophe here). Of course, this approach would meld nicely with any better record/label system. For starters: class <C>'name a where type <R>'name a :: * 'name :: a -> <R>'name a ''name :: <R>'name a -> a -> a instance <C>'name Foo where type <R>'name Foo = String 'name = Foo'name ''name = \v x -> x { Foo'name = v } There now -- I feel like TNDR is placating the muscle memory in our fingers that wants to type "f.name" ... and I hope we find a solution to replacing the tedium of so many "fooName" fields, and perhaps solve the record update ugliness as well! - Mark Mark Lentczner http://www.ozonehouse.com/mark/ IRC: mtnviewmark

On 12/11/2010, at 2:16 PM, John Lask wrote:
On 12/11/2010 9:22 AM, Richard O'Keefe wrote:
I'm afraid it's not a *convincing* use case. It's not convincing because here "owner" *means different things*.
consider "length" ...
I have records with the attribute length, length can be given as an Int, Double, Float or maybe as a constructed type "Length", length's use as a record selector would also clash with List.length. All these have the same denotation.
"All these have the same denotation"? I am extremely confused here. AH! You mean you call them all by the same name. Well yes, that's the problem, right there. I remind readers once again that in SML record selectors *don't* clash with names of functions. I am not concerned here to argue either for or against SML-style records and their selectors, only to point out that wanting *record fields* whose significance depends on the record they select from is *NOT* the same thing as TDNR in principle, so that arguments for that don't even come close to being arguments for TDNR as such.
should I then seporate into int_length, float_length, or use rec1_length, rec2_length etc etc...
No, the differing result types are an epiphenomenon of their differing semantics. The length of a piece of string is a physical length. The length of a lecture is a time. The length of a queue is a natural number (counting people). The length of a book is a positive integer (counting say pages, or words) The length of a vowel is a relative time. These quantities are measured differently, combined differently, and assessed differently. Calling them all "length" is a METAPHOR. (There are at least three metaphors in the list above: time-is-space, codex-is-scroll, and a form of metonomy.)
for proper name space management why should I have to define each record that defines a length field with different representation in distinct modules, or with different names for the field label when they denote the same thing?
But you just explained that while they may have the same denotation (the identifier), what it DENOTES is NOT the same (otherwise they could not be different types). As SML proves, having record-sensitive field names is a *different* question from Type Directed Name Resolution applied to plain function names.
This is easily handled in C, Pascal, PL/1, Cobol why not in Haskell ?
But it *isn't* handled *AT ALL* in any of those languages, let alone handled easily. In C, Pascal, PL/I, and COBOL field names are *not* values. C, Pascal, and PL/I let you pass functions as parameters to functions. But you cannot pass field names that way. The only thing you can do with a field name is apply it *immediately* to a record. And those languages don't have type variables, so when you apply a selector to a record, you know then and there what the type is. If what you want is some sort of record facility at least as good as SML's, fine. What I am arguing against is anything resembling Type Directed Name Resolution (alias ad hoc overloading) being applied to plain ordinary functions. (By the way, if the field names of a record type are visible outside its module, I start wondering why.)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 11/11/10 8:54 PM, Richard O'Keefe wrote:
I remind readers once again that in SML record selectors *don't* clash with names of functions. I am not concerned here to argue either for or against SML-style records and their selectors, only to point out that wanting *record fields* whose significance depends on the record they select from is *NOT* the same thing as TDNR in principle, so that arguments for that don't even come close to being arguments for TDNR as such.
My sentiments exactly. If people were to argue for SML-esque record selectors and the row-polymorphism that goes with them, I might be willing to throw in with that cause (or I might not, depending on the alternatives). However, that proposal is *very* different than the TDNR proposal. With row-polymorphism there's a decent chance of not shooting yourself in the face; there's a well-understood type theory that goes along with it, and it's been used in practice in other languages with a type system fairly similar to Haskell's. With TDNR, however, the situation is quite different. -- Live well, ~wren

On 11 November 2010 01:19, Richard O'Keefe
I'm not sure that it is desirable to have "many records in the same module" in the first place.
Amongst other reasons, http://www.haskell.org/haskellwiki/Mutually_recursive_modules -- Ozgur Akgun

On 12/11/2010, at 3:22 AM, Ozgur Akgun wrote:
On 11 November 2010 01:19, Richard O'Keefe
wrote: I'm not sure that it is desirable to have "many records in the same module" in the first place. Amongst other reasons, http://www.haskell.org/haskellwiki/Mutually_recursive_modules
The Programatica project showed that recursive modules *could* be implemented; if I remember correctly, their module resolution code was in pure Haskell 98. However, I'll grant you the incomplete implementation status of Haskell98 as an argument for fusing what would have been mutually recursive modules (although I suspect that two-level types may be better). That still isn't an argument for >>MANY<< records in the same module.

I agree with the people who want to decouple the dot-syntax from TDNR
itself. To quote myself from the publicly-editable wiki page:
"This might be a really dumb question, but is there any reason TDNR
needs to be tied to a new syntax for function application? It seems
strange to me to have one syntax for left-to-right function
application without TDNR, and then another for right-to-left
application with it. I would much rather gain TDNR for the existing
syntax, and then maybe introduce the dot operator as a separate option
if people want it, which I don't. The reason I don't is that (.) as
composition and ($) already work in one direction, which is the same
direction (`foo . bar . baz $ bla` and `foo $ bar $ baz $ bla` are
interchangeable), and while in a vacuum I might even prefer the
opposite direction which (.)-as-application uses, it is much more
important to be consistent. We have a vast body of functions already
written and designed to be convenient with the existing direction:
functions are generally of the form `f :: (what to do) -> (what to do
it with) -> (result)`, which lends itself well to partial
application/currying and chaining in the existing direction, but not
the other one. (Object oriented languages which use the dot operator
indeed also use the reverse order for their methods, with the object
first and the action second.) Also, reading expressions where
different parts work in different directions is very confusing. The
one major exception which works in the other direction is monadic
bind, (>>=), which I think was a (minor) mistake, and indeed I
frequently end up using (=<<) instead. Anyway, executive summary: TDNR
yea, dot operator nay."
Some further thoughts.
I would have TDNR apply only in cases where:
- The functions are all imported from different modules (so you can't
define overlapping names within the same module);
- All of the functions have an explicit type signature;
- The ambiguity can be resolved by looking at the type of the first
(taking currying into account, only) parameter of each function and,
looking at the type constructors from the outside in, comparing only
type constructors which are concrete types, rather than type variables
(with or without constraints). E.g.:
-- f :: Int -> [...] and f :: Char -> [...] could be resolved;
-- f :: Foo Int -> [...] and f :: Foo Char -> [...] could be resolved;
-- f :: Foo a -> [...] and f :: Bar b -> [...] could be resolved;
-- f :: Num a => a -> [...] and f :: IsString b => b -> [...] could
*not* be resolved (even if it is known that the argument type doesn't
satisfy both constraints);
-- f :: a Int -> [...] and f :: b Char -> [...] could *not* be
resolved (though I'm less sure about this one).
-- Going by the above, neither Foo nor Bar can be type functions.
-- With more than two functions, each possible pair has to meet the conditions.
I don't have any well-articulated arguments to support this idea, yet;
it mainly just "feels right". My intuition for TDNR is that it has no
connection to semantics, and it is not intended as a means of defining
an interface: it is merely a syntactic convenience. If you want to
define an interface, use a type class. TDNR would be a convenience for
the case where you have imported multiple modules using a function of
the same name with obviously different types (whether the functions do
similar or different things is beside the point). Comparing to C++
(though it's unlikely to help my case to mention that language here,
but whatever), I feel that type classes : TDNR :: virtual functions :
static overloading.
And, in any case, as a language extension nobody would be forced to
use it if they don't like it. (I personally would find it very
useful). I think the fact that language extensions need to meet (much)
lesser criteria than changes to the language standard itself is
plainly evidenced by the existence of IncoherentInstances, which
nobody in their right mind would ever consider standardizing (or, for
that matter, ever enabling).
On Wed, Nov 10, 2010 at 10:59 AM, John Smith
Type-directed name resolution, as originally proposed for Haskell', has now been proposed for GHC. Obvious benefits of this are that conflicting function names from imported modules can be used without qualification (verbose) or pseudo-Hungarian renaming (verbose, and requires that you control the source, and perform the same renaming in all dependencies). This is important for both readability and programming in the large, particularly where records are concerned, as the duplicate name problem cannot be alleviated with typeclasses, and it is often desirable to have the same field names for many records in the same module.
http://hackage.haskell.org/trac/ghc/ticket/4479 http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.

2010/11/11 Gábor Lehel
I agree with the people who want to decouple the dot-syntax from TDNR itself. To quote myself from the publicly-editable wiki page:
"This might be a really dumb question, but is there any reason TDNR needs to be tied to a new syntax for function application? It seems strange to me to have one syntax for left-to-right function application without TDNR, and then another for right-to-left application with it. I would much rather gain TDNR for the existing syntax, and then maybe introduce the dot operator as a separate option if people want it, which I don't. The reason I don't is that (.) as composition and ($) already work in one direction, which is the same direction (`foo . bar . baz $ bla` and `foo $ bar $ baz $ bla` are interchangeable), and while in a vacuum I might even prefer the opposite direction which (.)-as-application uses, it is much more important to be consistent. We have a vast body of functions already written and designed to be convenient with the existing direction: functions are generally of the form `f :: (what to do) -> (what to do it with) -> (result)`, which lends itself well to partial application/currying and chaining in the existing direction, but not the other one. (Object oriented languages which use the dot operator indeed also use the reverse order for their methods, with the object first and the action second.) Also, reading expressions where different parts work in different directions is very confusing. The one major exception which works in the other direction is monadic bind, (>>=), which I think was a (minor) mistake, and indeed I frequently end up using (=<<) instead. Anyway, executive summary: TDNR yea, dot operator nay."
Some further thoughts.
I would have TDNR apply only in cases where: - The functions are all imported from different modules (so you can't define overlapping names within the same module); - All of the functions have an explicit type signature; - The ambiguity can be resolved by looking at the type of the first (taking currying into account, only) parameter of each function and, looking at the type constructors from the outside in, comparing only type constructors which are concrete types, rather than type variables (with or without constraints). E.g.: -- f :: Int -> [...] and f :: Char -> [...] could be resolved; -- f :: Foo Int -> [...] and f :: Foo Char -> [...] could be resolved; -- f :: Foo a -> [...] and f :: Bar b -> [...] could be resolved; -- f :: Num a => a -> [...] and f :: IsString b => b -> [...] could *not* be resolved (even if it is known that the argument type doesn't satisfy both constraints); -- f :: a Int -> [...] and f :: b Char -> [...] could *not* be resolved (though I'm less sure about this one). -- Going by the above, neither Foo nor Bar can be type functions. -- With more than two functions, each possible pair has to meet the conditions.
I forgot to mention: some kind of similar criteria should probably apply to the function where 'f' is used (again going by the above examples) and/or its argument as well. E.g. it should not be possible to define "g a = f a" and have f be resolved by TDNR when g is used (even if all of the in-scope functions with the name 'f' meet the previous criteria), because TDNR is not duck typing.
I don't have any well-articulated arguments to support this idea, yet; it mainly just "feels right". My intuition for TDNR is that it has no connection to semantics, and it is not intended as a means of defining an interface: it is merely a syntactic convenience. If you want to define an interface, use a type class. TDNR would be a convenience for the case where you have imported multiple modules using a function of the same name with obviously different types (whether the functions do similar or different things is beside the point). Comparing to C++ (though it's unlikely to help my case to mention that language here, but whatever), I feel that type classes : TDNR :: virtual functions : static overloading.
And, in any case, as a language extension nobody would be forced to use it if they don't like it. (I personally would find it very useful). I think the fact that language extensions need to meet (much) lesser criteria than changes to the language standard itself is plainly evidenced by the existence of IncoherentInstances, which nobody in their right mind would ever consider standardizing (or, for that matter, ever enabling).
On Wed, Nov 10, 2010 at 10:59 AM, John Smith
wrote: Type-directed name resolution, as originally proposed for Haskell', has now been proposed for GHC. Obvious benefits of this are that conflicting function names from imported modules can be used without qualification (verbose) or pseudo-Hungarian renaming (verbose, and requires that you control the source, and perform the same renaming in all dependencies). This is important for both readability and programming in the large, particularly where records are concerned, as the duplicate name problem cannot be alleviated with typeclasses, and it is often desirable to have the same field names for many records in the same module.
http://hackage.haskell.org/trac/ghc/ticket/4479 http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolutio...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.
-- Work is punishment for failing to procrastinate effectively.

On 11/11/2010, at 10:33 PM, Gábor Lehel wrote:
I would have TDNR apply only in cases where: ... - The ambiguity can be resolved by looking at the type of the first (taking currying into account, only) parameter of each function and, looking at the type constructors from the outside in, comparing only type constructors which are concrete types, rather than type variables (with or without constraints).
This just feels so wrong. One of the joys of types in Haskell and of overloading in Ada is that it depends on *all* the arguments of a function *and* the result. I note that record field overloading can be put in a language without providing ad hoc polymorphism for any other functions. A little ML: Given type t1 = {a: int, b: string}; type t2 = {a: string, b: int}; val x1 : t1 = {a = 1, b = "2"}; val x2 : t2 = {b = 2, a = "1"}; this interaction followed: - (#a x1, #a x2, #b x1, #b x2); val it = (1,"1","2",2) : int * string * string * int Here we had #a : t1 -> int #b : t1 -> string #a : t2 -> string #b : t2 -> int The consequence is that when I see val N = #capacity derived () I don't know what capacity means for sure, but I *do* know that it is a record field, so I have some idea what to look for. It turns out that there are four possibilities but for two of them () would not be a legal argument, so there are only two possibilities. I note that there is a reason for having quite a few records in a module with many shared field names at different types, which I had not thought of. That is the practice of passing a record as a function's sole argument in order to get the effect of keyword arguments, fairly popular in SML: val max_flow : { graph : ('n,'e,'g) Graph.graph, s : Graph.node_id, t : Graph.node_id, capacity : 'e Graph.edge -> Num.elem, flows : 'e Graph.edge * Num.elem -> unit } -> Num.elem val min_cost_max_flow : { graph : ('n,'e,'g) Graph.graph, s : Graph.node_id, t : Graph.node_id, capacity : 'e Graph.edge -> Num.elem, cost : 'e Graph.edge -> Num.elem, flows : 'e Graph.edge * Num.elem -> unit } -> Num.elem There is no intention here to have lots of values of these record types. They are anonymous, after all. This case needs to be considered separately from other cases.
And, in any case, as a language extension nobody would be forced to use it if they don't like it.
Wrong. They would not be forced to use it in their own code, but they *WOULD* be forced to read it in other people's code. (Why so much focus on the writers and so little on the readers?)
participants (30)
-
Albert Y. C. Lai
-
Alexander Kjeldaas
-
Andrew Coppin
-
Ben Lippmeier
-
Claus Reinke
-
Dan Doel
-
David Menendez
-
Erik Hesselink
-
Evan Laforge
-
Gábor Lehel
-
Henning Thielemann
-
John Lask
-
John Smith
-
Jonathan Geddes
-
JP Moresmau
-
Ketil Malde
-
Lauri Alanko
-
Luke Palmer
-
Malcolm Wallace
-
Mark Lentczner
-
Michael Snoyman
-
Miguel Mitrofanov
-
Neil Brown
-
Ozgur Akgun
-
Richard O'Keefe
-
Ryan Ingram
-
Sebastian Fischer
-
Stephen Tetley
-
wren ng thornton
-
Yves Parès