Re: Better Records was Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-15 Thread Erik Hesselink
On Fri, Nov 12, 2010 at 22:48, Jonathan Geddes wrote: >> 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 update

[Haskell-cafe] Type-Directed Name Resolution for Records?

2010-11-15 Thread John Smith
Two significant points which have emerged from the TDNR thread are: -The wiki page combines two orthogonal proposals: type-directed name resolution, which requires no special syntax, and the x.f syntax, which does not require TDNR. -Implementing both proposals may be a desired fix for the record

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-15 Thread Richard O'Keefe
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-15 Thread Henning Thielemann
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 ac

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-15 Thread Richard O'Keefe
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 puzzl

Re: Better Records was Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-12 Thread Stephen Tetley
On 12 November 2010 21:48, Jonathan Geddes wrote: > > 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

Re: Better Records was Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-12 Thread 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. The jist of it is in the following: >someUpdate :: MyRecord -> MyRecord >someUpdate myRecord = myRecord > { fie

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-12 Thread Stephen Tetley
On 12 November 2010 20:33, Malcolm Wallace wrote: > 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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-12 Thread Andrew Coppin
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,

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-12 Thread Malcolm Wallace
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 w

Re: Better Records was Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-12 Thread 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 thi

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-12 Thread Andrew Coppin
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Ben Lippmeier
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 backf

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Mark Lentczner
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

Re: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread David Menendez
On Thu, Nov 11, 2010 at 10:00 PM, John Lask wrote: >> On Thu, Nov 11, 2010 at 8:16 PM, John Lask  wrote: >>> >>> 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 >>> r

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Sebastian Fischer
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 initial

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread wren ng thornton
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 significa

Re: Better Records was Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Evan Laforge
> 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 sy

Re: Fwd: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Donn Cave
Quoth John Lask , ... > By the way I am not arguing for TDNR, merely that all is not well with > haskell records. And you have a lot of company there, but the discussion is taking place in a thread named "Type Directed Name Resolution". When that has been put to rest, let's talk about Haskell rec

Fwd: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask
On Thu, Nov 11, 2010 at 8:16 PM, John Lask wrote: 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 de

Fwd: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask
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 a

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread David Menendez
On Thu, Nov 11, 2010 at 8:16 PM, John Lask wrote: > 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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask
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 } J

Better Records was Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread John Lask
> > 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 record

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe
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, bec

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe
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 cam

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe
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, co

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Richard O'Keefe
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 th

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Claus Reinke
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Malcolm Wallace
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Ozgur Akgun
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 -- Ozgur Akgun __

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Gábor Lehel
On Thu, Nov 11, 2010 at 2:59 PM, Miguel Mitrofanov wrote: > > > 11.11.2010 16:53, Stephen Tetley пишет: >> >> On 11 November 2010 13:10, Lauri Alanko  wrote: >> >>> {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, >>> FunctionalDependencies #-} >>> >>> data PetOwner >>> data FurnitureOwner >>>

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread 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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread 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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Michael Snoyman
On Thu, Nov 11, 2010 at 3:10 PM, Lauri Alanko wrote: > 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 s

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread 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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Michael Snoyman
On Thu, Nov 11, 2010 at 2:24 PM, Lauri Alanko wrote: > 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 fiel

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread 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 > sel

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Gábor Lehel
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 se

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread 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 synt

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Luke Palmer
On Thu, Nov 11, 2010 at 1:41 AM, Luke Palmer wrote: > 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. >>> >> >>

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread 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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread 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 s

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Ketil Malde
"Richard O'Keefe" writes: >> 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 f

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Sebastian Fischer
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-sco

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Richard O'Keefe
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 =

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Richard O'Keefe
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Richard O'Keefe
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 lan

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread wren ng thornton
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 fee

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Alexander Kjeldaas
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Dan Doel
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 p

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Ryan Ingram
On Wed, Nov 10, 2010 at 11:08 AM, Lauri Alanko wrote: > 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, o

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Dan Doel
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 certainl

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Lauri Alanko
On Wed, Nov 10, 2010 at 11:59:28AM +0200, John Smith wrote: > http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution 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 postf

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Stephen Tetley
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread 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 Eng

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Ketil Malde
Neil Brown writes: > 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 b

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Evan Laforge
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 i

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Yves Parès
> 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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread 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 tha

[Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread 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 th

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Stephen Tetley
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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread 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

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread JP Moresmau
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 b

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Ozgur Akgun
On 10 November 2010 10:56, Ozgur Akgun wrote: > 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, cur

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread 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 getN

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-10 Thread Ketil Malde
John Smith writes: > 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 a