Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-28 Thread Chris Smith
+1

While it might work for teaching, it's not reasonable to ask software
developers who want to write useful software to depend on haskell98
instead of base if they want more relevant types.

I'd go one step further and say that we're not just talking about
whether someone is an "advanced" user either.  I'm probably among the
more advanced of Haskell users, but I'd still rather see specialized
type signatures in cases where one specific instance is far more
common than the others.  Yes, I know that certain combinators like
(***) and (&&&) are useful for functions, for example.  It still makes
me less productive to have those things stuffed off in a corner where
they are difficult to get to, and described in needlessly abstract
language.

I honestly can't understand the viewpoint that says that having the
compiler choose the unique most general type for imported symbols (or
give an error if none exists) is too complicated, yet programmers
manually substituting common instances into type signatures is no big
deal.  The first is fairly obvious work done by the compiler, which
the second needs programmers (yes, even experienced ones) to
occasionally get out a pencil and paper to work out the details.

On Tue, May 28, 2013 at 1:23 AM, Daniel Gorín  wrote:
> It is not only a matter of teaching, I think. After first learning the very 
> basics of a language, browsing the libraries that come included is a more or 
> less standard way of getting more acquainted with it. By including only the 
> abstract versions we are making it much harder to learn the common idioms.
>
> For instance, at the moment, how likely is that someone will start using 
> (&&&), (***), (+++) or any of the useful combinators in Control.Arrow from 
> reading its haddock? These are very handy functions, easy to understand when 
> specialized to (->), but are usually reserved for advanced users since they 
> are presented only in their most general way. With an extension like this one 
> available, one could propose including specialized versions of them in 
> Data.Function and/or Data.Tuple/Data.Either; today it would be a very bad 
> idea due to the clash with Control.Arrow!
>
> Daniel
>
> On May 28, 2013, at 3:27 AM, Edward A Kmett wrote:
>
>> This is basically what you get by default already with the raw proposal 
>> we've been talking about -- the Preludes in the haskell98 and haskell2010 
>> remain unmodified by this proposal and are available for teaching use.
>>
>> Sent from my iPhone
>>
>> On May 27, 2013, at 8:53 PM, Andrew Farmer  wrote:
>>
>>> I generally agree with Iavor's points, but if this is such an issue, why 
>>> not make Prelude more general by default and have a special 'Prelude.Basic' 
>>> with the more specific type signatures for beginners? The general Prelude 
>>> would be implicitly imported as now, unless the module imported 
>>> Prelude.Basic unqualified. Then make Hackage warn/reject packages that use 
>>> Prelude.Basic.
>>>
>>> Tutorials/Books would have to tell readers to add a magic "import 
>>> Prelude.Basic" at the beginning of their source files, but tutorials for 
>>> other languages do this (public static void main(..)?) to relatively little 
>>> complaint.
>>>
>>> Sorry, I'm sure this has been proposed before... but the proposed extension 
>>> seems complicated to avoid some qualified imports/hidings. If we really 
>>> want people to use Foldable's foldr by default, then make it the default 
>>> and let beginners add a magic line once per file to get simpler types.
>>>
>>> Andrew
>>>
>>>
>>> On Mon, May 27, 2013 at 5:07 PM, Daniel Gorín  wrote:
>>> Hi Iavor,
>>>
>>> On May 27, 2013, at 6:18 PM, Iavor Diatchki wrote:
>>>
>>> > Hello,
>>> >
>>> >
>>> > On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín  wrote:
>>> > On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
>>> >
>>> >> > How about (in Haskell98)
>>> >> >
>>> >> >   module Data.List ( foldr, ...)
>>> >> >   import qualified Data.Foldable
>>> >> >   foldr :: (a -> b -> b) -> b -> [a] -> b
>>> >> >   foldr = Data.Foldable.foldr
>>> >>
>>> >> It would not be the same! Using your example one will get that the 
>>> >> following fails to compile:
>>> >>
>>> >> > import Data.List
>>> >> > import Data.Foldable
>>> >> > f = foldr
>>> >>
>>> >> The problem is that Data.List.foldr and Data.Foldable.foldr are here 
>>> >> different symbols with the same name.
>>> >> This is precisely why Foldable, Traversable, Category, etc are awkward 
>>> >> to use. The proposal is to make Data.List reexport Data.Foldable.foldr 
>>> >> (with a more specialized type) so that the module above can be accepted.
>>> >>
>>> >
>>> > I think that it is perfectly reasonable for this to fail to compile---to 
>>> > me, this sort of implicit shadowing based on what extensions are turned 
>>> > on would be very confusing.  It may seem obvious with a well-known 
>>> > example, such as `foldr`, but I can easily imagine getting a headache 
>>> > trying to figure out a new lib

Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-28 Thread Daniel Gorín
It is not only a matter of teaching, I think. After first learning the very 
basics of a language, browsing the libraries that come included is a more or 
less standard way of getting more acquainted with it. By including only the 
abstract versions we are making it much harder to learn the common idioms.

For instance, at the moment, how likely is that someone will start using (&&&), 
(***), (+++) or any of the useful combinators in Control.Arrow from reading its 
haddock? These are very handy functions, easy to understand when specialized to 
(->), but are usually reserved for advanced users since they are presented only 
in their most general way. With an extension like this one available, one could 
propose including specialized versions of them in Data.Function and/or 
Data.Tuple/Data.Either; today it would be a very bad idea due to the clash with 
Control.Arrow!

Daniel

On May 28, 2013, at 3:27 AM, Edward A Kmett wrote:

> This is basically what you get by default already with the raw proposal we've 
> been talking about -- the Preludes in the haskell98 and haskell2010 remain 
> unmodified by this proposal and are available for teaching use.
> 
> Sent from my iPhone
> 
> On May 27, 2013, at 8:53 PM, Andrew Farmer  wrote:
> 
>> I generally agree with Iavor's points, but if this is such an issue, why not 
>> make Prelude more general by default and have a special 'Prelude.Basic' with 
>> the more specific type signatures for beginners? The general Prelude would 
>> be implicitly imported as now, unless the module imported Prelude.Basic 
>> unqualified. Then make Hackage warn/reject packages that use Prelude.Basic.
>> 
>> Tutorials/Books would have to tell readers to add a magic "import 
>> Prelude.Basic" at the beginning of their source files, but tutorials for 
>> other languages do this (public static void main(..)?) to relatively little 
>> complaint.
>> 
>> Sorry, I'm sure this has been proposed before... but the proposed extension 
>> seems complicated to avoid some qualified imports/hidings. If we really want 
>> people to use Foldable's foldr by default, then make it the default and let 
>> beginners add a magic line once per file to get simpler types.
>> 
>> Andrew
>> 
>> 
>> On Mon, May 27, 2013 at 5:07 PM, Daniel Gorín  wrote:
>> Hi Iavor,
>> 
>> On May 27, 2013, at 6:18 PM, Iavor Diatchki wrote:
>> 
>> > Hello,
>> >
>> >
>> > On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín  wrote:
>> > On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
>> >
>> >> > How about (in Haskell98)
>> >> >
>> >> >   module Data.List ( foldr, ...)
>> >> >   import qualified Data.Foldable
>> >> >   foldr :: (a -> b -> b) -> b -> [a] -> b
>> >> >   foldr = Data.Foldable.foldr
>> >>
>> >> It would not be the same! Using your example one will get that the 
>> >> following fails to compile:
>> >>
>> >> > import Data.List
>> >> > import Data.Foldable
>> >> > f = foldr
>> >>
>> >> The problem is that Data.List.foldr and Data.Foldable.foldr are here 
>> >> different symbols with the same name.
>> >> This is precisely why Foldable, Traversable, Category, etc are awkward to 
>> >> use. The proposal is to make Data.List reexport Data.Foldable.foldr (with 
>> >> a more specialized type) so that the module above can be accepted.
>> >>
>> >
>> > I think that it is perfectly reasonable for this to fail to compile---to 
>> > me, this sort of implicit shadowing based on what extensions are turned on 
>> > would be very confusing.  It may seem obvious with a well-known example, 
>> > such as `foldr`, but I can easily imagine getting a headache trying to 
>> > figure out a new library that makes uses the proposed feature in anger :)
>> 
>> I understand your concern, but I don't quite see how a library could abuse 
>> this feature. I mean, a library could export the same symbol with different 
>> specialized types in various modules, but you, the user of the library, will 
>> see them as different symbols with conflicting name, just like now you see 
>> symbols Prelude.foldr and Data.Foldable.foldr exported by base... unless, of 
>> course, you specifically activate the extension (the one called 
>> MoreSpecificImports in my first mail). That is, it would be an opt-in 
>> feature.
>> 
>> > Also, using module-level language extensions does not seem like the right 
>> > tool for this task: what if I wanted to use the most general version of 
>> > one symbol, but the most specific version of another?
>> 
>> Do you have a particular example in mind? The more general version of every 
>> symbol can be used wherever the more specialized one fits, and in the 
>> (seemingly rare?) case where the extra polymorphism may harm you and that 
>> adding a type annotation is not convenient enough, you could just hide the 
>> import of more the general  version. Do you anticipate this to be a common 
>> scenario?
>> 
>> >  One needs a more fine grained tool, and I think that current module 
>> > system already provides enough features

Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-27 Thread Edward A Kmett
This is basically what you get by default already with the raw proposal we've 
been talking about -- the Preludes in the haskell98 and haskell2010 remain 
unmodified by this proposal and are available for teaching use.

Sent from my iPhone

On May 27, 2013, at 8:53 PM, Andrew Farmer  wrote:

> I generally agree with Iavor's points, but if this is such an issue, why not 
> make Prelude more general by default and have a special 'Prelude.Basic' with 
> the more specific type signatures for beginners? The general Prelude would be 
> implicitly imported as now, unless the module imported Prelude.Basic 
> unqualified. Then make Hackage warn/reject packages that use Prelude.Basic.
> 
> Tutorials/Books would have to tell readers to add a magic "import 
> Prelude.Basic" at the beginning of their source files, but tutorials for 
> other languages do this (public static void main(..)?) to relatively little 
> complaint.
> 
> Sorry, I'm sure this has been proposed before... but the proposed extension 
> seems complicated to avoid some qualified imports/hidings. If we really want 
> people to use Foldable's foldr by default, then make it the default and let 
> beginners add a magic line once per file to get simpler types.
> 
> Andrew
> 
> 
> On Mon, May 27, 2013 at 5:07 PM, Daniel Gorín  wrote:
>> Hi Iavor,
>> 
>> On May 27, 2013, at 6:18 PM, Iavor Diatchki wrote:
>> 
>> > Hello,
>> >
>> >
>> > On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín  wrote:
>> > On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
>> >
>> >> > How about (in Haskell98)
>> >> >
>> >> >   module Data.List ( foldr, ...)
>> >> >   import qualified Data.Foldable
>> >> >   foldr :: (a -> b -> b) -> b -> [a] -> b
>> >> >   foldr = Data.Foldable.foldr
>> >>
>> >> It would not be the same! Using your example one will get that the 
>> >> following fails to compile:
>> >>
>> >> > import Data.List
>> >> > import Data.Foldable
>> >> > f = foldr
>> >>
>> >> The problem is that Data.List.foldr and Data.Foldable.foldr are here 
>> >> different symbols with the same name.
>> >> This is precisely why Foldable, Traversable, Category, etc are awkward to 
>> >> use. The proposal is to make Data.List reexport Data.Foldable.foldr (with 
>> >> a more specialized type) so that the module above can be accepted.
>> >>
>> >
>> > I think that it is perfectly reasonable for this to fail to compile---to 
>> > me, this sort of implicit shadowing based on what extensions are turned on 
>> > would be very confusing.  It may seem obvious with a well-known example, 
>> > such as `foldr`, but I can easily imagine getting a headache trying to 
>> > figure out a new library that makes uses the proposed feature in anger :)
>> 
>> I understand your concern, but I don't quite see how a library could abuse 
>> this feature. I mean, a library could export the same symbol with different 
>> specialized types in various modules, but you, the user of the library, will 
>> see them as different symbols with conflicting name, just like now you see 
>> symbols Prelude.foldr and Data.Foldable.foldr exported by base... unless, of 
>> course, you specifically activate the extension (the one called 
>> MoreSpecificImports in my first mail). That is, it would be an opt-in 
>> feature.
>> 
>> > Also, using module-level language extensions does not seem like the right 
>> > tool for this task: what if I wanted to use the most general version of 
>> > one symbol, but the most specific version of another?
>> 
>> Do you have a particular example in mind? The more general version of every 
>> symbol can be used wherever the more specialized one fits, and in the 
>> (seemingly rare?) case where the extra polymorphism may harm you and that 
>> adding a type annotation is not convenient enough, you could just hide the 
>> import of more the general  version. Do you anticipate this to be a common 
>> scenario?
>> 
>> >  One needs a more fine grained tool, and I think that current module 
>> > system already provides enough features to do so (e.g., explicit export 
>> > lists, `hiding` clauses`, and qualified imports).  For example, it really 
>> > does not seem that inconvenient (and, in fact, I find it helpful!) to 
>> > write the following:
>> >
>> > import Data.List hiding (foldr)
>> > import Data.Foldable
>> 
>> But this doesn't scale that well, IMO. In real code even restricted to the 
>> the base package the hiding clauses can get quite long and qualifying basic 
>> polymorphic functions starts to feel like polymorphism done wrong.
>> 
>> This can very well be just a matter of taste, but apparently so many people 
>> have strong feelings about this issue that it is seriously being proposed to 
>> move Foldable and Traversable to the Prelude, removing all the monomorphic 
>> counterparts (that is, make Prelude export the unspecialized versions). 
>> While this would be certainly convenient for me, I think it would be an 
>> unfortunate move: removing concrete (monomorphic) func

Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-27 Thread Andrew Farmer
I generally agree with Iavor's points, but if this is such an issue, why
not make Prelude more general by default and have a special 'Prelude.Basic'
with the more specific type signatures for beginners? The general Prelude
would be implicitly imported as now, unless the module imported
Prelude.Basic unqualified. Then make Hackage warn/reject packages that use
Prelude.Basic.

Tutorials/Books would have to tell readers to add a magic "import
Prelude.Basic" at the beginning of their source files, but tutorials for
other languages do this (public static void main(..)?) to relatively little
complaint.

Sorry, I'm sure this has been proposed before... but the proposed extension
seems complicated to avoid some qualified imports/hidings. If we really
want people to use Foldable's foldr by default, then make it the default
and let beginners add a magic line once per file to get simpler types.

Andrew


On Mon, May 27, 2013 at 5:07 PM, Daniel Gorín  wrote:

> Hi Iavor,
>
> On May 27, 2013, at 6:18 PM, Iavor Diatchki wrote:
>
> > Hello,
> >
> >
> > On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín  wrote:
> > On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
> >
> >> > How about (in Haskell98)
> >> >
> >> >   module Data.List ( foldr, ...)
> >> >   import qualified Data.Foldable
> >> >   foldr :: (a -> b -> b) -> b -> [a] -> b
> >> >   foldr = Data.Foldable.foldr
> >>
> >> It would not be the same! Using your example one will get that the
> following fails to compile:
> >>
> >> > import Data.List
> >> > import Data.Foldable
> >> > f = foldr
> >>
> >> The problem is that Data.List.foldr and Data.Foldable.foldr are here
> different symbols with the same name.
> >> This is precisely why Foldable, Traversable, Category, etc are awkward
> to use. The proposal is to make Data.List reexport Data.Foldable.foldr
> (with a more specialized type) so that the module above can be accepted.
> >>
> >
> > I think that it is perfectly reasonable for this to fail to compile---to
> me, this sort of implicit shadowing based on what extensions are turned on
> would be very confusing.  It may seem obvious with a well-known example,
> such as `foldr`, but I can easily imagine getting a headache trying to
> figure out a new library that makes uses the proposed feature in anger :)
>
> I understand your concern, but I don't quite see how a library could abuse
> this feature. I mean, a library could export the same symbol with different
> specialized types in various modules, but you, the user of the library,
> will see them as different symbols with conflicting name, just like now you
> see symbols Prelude.foldr and Data.Foldable.foldr exported by base...
> unless, of course, you specifically activate the extension (the one called
> MoreSpecificImports in my first mail). That is, it would be an opt-in
> feature.
>
> > Also, using module-level language extensions does not seem like the
> right tool for this task: what if I wanted to use the most general version
> of one symbol, but the most specific version of another?
>
> Do you have a particular example in mind? The more general version of
> every symbol can be used wherever the more specialized one fits, and in the
> (seemingly rare?) case where the extra polymorphism may harm you and that
> adding a type annotation is not convenient enough, you could just hide the
> import of more the general  version. Do you anticipate this to be a common
> scenario?
>
> >  One needs a more fine grained tool, and I think that current module
> system already provides enough features to do so (e.g., explicit export
> lists, `hiding` clauses`, and qualified imports).  For example, it really
> does not seem that inconvenient (and, in fact, I find it helpful!) to write
> the following:
> >
> > import Data.List hiding (foldr)
> > import Data.Foldable
>
> But this doesn't scale that well, IMO. In real code even restricted to the
> the base package the hiding clauses can get quite long and qualifying basic
> polymorphic functions starts to feel like polymorphism done wrong.
>
> This can very well be just a matter of taste, but apparently so many
> people have strong feelings about this issue that it is seriously being
> proposed to move Foldable and Traversable to the Prelude, removing all the
> monomorphic counterparts (that is, make Prelude export the unspecialized
> versions). While this would be certainly convenient for me, I think it
> would be an unfortunate move: removing concrete (monomorphic) functions in
> favor of abstract versions will make a language that is already hard to
> learn, even harder (but there was a long enough thread in the libraries
> mailing list about this already!). In any case this proposal is an attempt
> to resolve this tension without "penalizing" any of the sides.
>
> Thanks,
> Daniel
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgo

Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-27 Thread Chris Smith
I agree that it would be unfortunate to complicate the Prelude
definitions of foldr and such by generalizing to type classes like
Foldable.  This proposal seems attractive to me as a way to reconcile
abstraction when it's needed, and simplicity for beginners.  However,
it does seem like a common pattern might be to want to re-export a
more generic symbol alongside a rewrite rule that substitutes a more
efficient implementation for a specific type.  Consider Text,
ByteString, and Vector, for example.  Is that doable with rewrite
rules and this proposal?

I'd also point out that the first of the two (-XMoreSpecificExports)
would be convenient even without the other.  Many people already
routinely list type signatures in comments after each symbol of the
export list.  This would just allow the compiler to check and enforce
the contracts that people are already documenting in comments.  Adding
optional type checking where people are already writing type
signatures anyway seems like an obvious win.

On Mon, May 27, 2013 at 5:07 PM, Daniel Gorín  wrote:
> Hi Iavor,
>
> On May 27, 2013, at 6:18 PM, Iavor Diatchki wrote:
>
>> Hello,
>>
>>
>> On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín  wrote:
>> On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
>>
>>> > How about (in Haskell98)
>>> >
>>> >   module Data.List ( foldr, ...)
>>> >   import qualified Data.Foldable
>>> >   foldr :: (a -> b -> b) -> b -> [a] -> b
>>> >   foldr = Data.Foldable.foldr
>>>
>>> It would not be the same! Using your example one will get that the 
>>> following fails to compile:
>>>
>>> > import Data.List
>>> > import Data.Foldable
>>> > f = foldr
>>>
>>> The problem is that Data.List.foldr and Data.Foldable.foldr are here 
>>> different symbols with the same name.
>>> This is precisely why Foldable, Traversable, Category, etc are awkward to 
>>> use. The proposal is to make Data.List reexport Data.Foldable.foldr (with a 
>>> more specialized type) so that the module above can be accepted.
>>>
>>
>> I think that it is perfectly reasonable for this to fail to compile---to me, 
>> this sort of implicit shadowing based on what extensions are turned on would 
>> be very confusing.  It may seem obvious with a well-known example, such as 
>> `foldr`, but I can easily imagine getting a headache trying to figure out a 
>> new library that makes uses the proposed feature in anger :)
>
> I understand your concern, but I don't quite see how a library could abuse 
> this feature. I mean, a library could export the same symbol with different 
> specialized types in various modules, but you, the user of the library, will 
> see them as different symbols with conflicting name, just like now you see 
> symbols Prelude.foldr and Data.Foldable.foldr exported by base... unless, of 
> course, you specifically activate the extension (the one called 
> MoreSpecificImports in my first mail). That is, it would be an opt-in feature.
>
>> Also, using module-level language extensions does not seem like the right 
>> tool for this task: what if I wanted to use the most general version of one 
>> symbol, but the most specific version of another?
>
> Do you have a particular example in mind? The more general version of every 
> symbol can be used wherever the more specialized one fits, and in the 
> (seemingly rare?) case where the extra polymorphism may harm you and that 
> adding a type annotation is not convenient enough, you could just hide the 
> import of more the general  version. Do you anticipate this to be a common 
> scenario?
>
>>  One needs a more fine grained tool, and I think that current module system 
>> already provides enough features to do so (e.g., explicit export lists, 
>> `hiding` clauses`, and qualified imports).  For example, it really does not 
>> seem that inconvenient (and, in fact, I find it helpful!) to write the 
>> following:
>>
>> import Data.List hiding (foldr)
>> import Data.Foldable
>
> But this doesn't scale that well, IMO. In real code even restricted to the 
> the base package the hiding clauses can get quite long and qualifying basic 
> polymorphic functions starts to feel like polymorphism done wrong.
>
> This can very well be just a matter of taste, but apparently so many people 
> have strong feelings about this issue that it is seriously being proposed to 
> move Foldable and Traversable to the Prelude, removing all the monomorphic 
> counterparts (that is, make Prelude export the unspecialized versions). While 
> this would be certainly convenient for me, I think it would be an unfortunate 
> move: removing concrete (monomorphic) functions in favor of abstract versions 
> will make a language that is already hard to learn, even harder (but there 
> was a long enough thread in the libraries mailing list about this already!). 
> In any case this proposal is an attempt to resolve this tension without 
> "penalizing" any of the sides.
>
> Thanks,
> Daniel
> 

Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-27 Thread Daniel Gorín
Hi Iavor,

On May 27, 2013, at 6:18 PM, Iavor Diatchki wrote:

> Hello,
> 
> 
> On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín  wrote:
> On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
> 
>> > How about (in Haskell98)
>> >
>> >   module Data.List ( foldr, ...)
>> >   import qualified Data.Foldable
>> >   foldr :: (a -> b -> b) -> b -> [a] -> b
>> >   foldr = Data.Foldable.foldr
>> 
>> It would not be the same! Using your example one will get that the following 
>> fails to compile:
>> 
>> > import Data.List
>> > import Data.Foldable
>> > f = foldr
>> 
>> The problem is that Data.List.foldr and Data.Foldable.foldr are here 
>> different symbols with the same name.
>> This is precisely why Foldable, Traversable, Category, etc are awkward to 
>> use. The proposal is to make Data.List reexport Data.Foldable.foldr (with a 
>> more specialized type) so that the module above can be accepted.
>> 
> 
> I think that it is perfectly reasonable for this to fail to compile---to me, 
> this sort of implicit shadowing based on what extensions are turned on would 
> be very confusing.  It may seem obvious with a well-known example, such as 
> `foldr`, but I can easily imagine getting a headache trying to figure out a 
> new library that makes uses the proposed feature in anger :)

I understand your concern, but I don't quite see how a library could abuse this 
feature. I mean, a library could export the same symbol with different 
specialized types in various modules, but you, the user of the library, will 
see them as different symbols with conflicting name, just like now you see 
symbols Prelude.foldr and Data.Foldable.foldr exported by base... unless, of 
course, you specifically activate the extension (the one called 
MoreSpecificImports in my first mail). That is, it would be an opt-in feature.

> Also, using module-level language extensions does not seem like the right 
> tool for this task: what if I wanted to use the most general version of one 
> symbol, but the most specific version of another?

Do you have a particular example in mind? The more general version of every 
symbol can be used wherever the more specialized one fits, and in the 
(seemingly rare?) case where the extra polymorphism may harm you and that 
adding a type annotation is not convenient enough, you could just hide the 
import of more the general  version. Do you anticipate this to be a common 
scenario?

>  One needs a more fine grained tool, and I think that current module system 
> already provides enough features to do so (e.g., explicit export lists, 
> `hiding` clauses`, and qualified imports).  For example, it really does not 
> seem that inconvenient (and, in fact, I find it helpful!) to write the 
> following:
> 
> import Data.List hiding (foldr)
> import Data.Foldable

But this doesn't scale that well, IMO. In real code even restricted to the the 
base package the hiding clauses can get quite long and qualifying basic 
polymorphic functions starts to feel like polymorphism done wrong.

This can very well be just a matter of taste, but apparently so many people 
have strong feelings about this issue that it is seriously being proposed to 
move Foldable and Traversable to the Prelude, removing all the monomorphic 
counterparts (that is, make Prelude export the unspecialized versions). While 
this would be certainly convenient for me, I think it would be an unfortunate 
move: removing concrete (monomorphic) functions in favor of abstract versions 
will make a language that is already hard to learn, even harder (but there was 
a long enough thread in the libraries mailing list about this already!). In any 
case this proposal is an attempt to resolve this tension without "penalizing" 
any of the sides. 

Thanks,
Daniel
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-27 Thread Iavor Diatchki
Hello,


On Fri, May 24, 2013 at 12:42 AM, Daniel Gorín  wrote:

> On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
>
> > How about (in Haskell98)
> >
> >   module Data.List ( foldr, ...)
> >   import qualified Data.Foldable
> >   foldr :: (a -> b -> b) -> b -> [a] -> b
> >   foldr = Data.Foldable.foldr
>
> It would not be the same! Using your example one will get that the
> following fails to compile:
>
> > import Data.List
> > import Data.Foldable
> > f = foldr
>
> The problem is that Data.List.foldr and Data.Foldable.foldr are here
> different symbols with the same name.
> This is precisely why Foldable, Traversable, Category, etc are awkward to
> use. The proposal is to make Data.List reexport Data.Foldable.foldr (with a
> more specialized type) so that the module above can be accepted.
>
>
I think that it is perfectly reasonable for this to fail to compile---to
me, this sort of implicit shadowing based on what extensions are turned on
would be very confusing.  It may seem obvious with a well-known example,
such as `foldr`, but I can easily imagine getting a headache trying to
figure out a new library that makes uses the proposed feature in anger :)

Also, using module-level language extensions does not seem like the right
tool for this task: what if I wanted to use the most general version of one
symbol, but the most specific version of another?  One needs a more fine
grained tool, and I think that current module system already provides
enough features to do so (e.g., explicit export lists, `hiding` clauses`,
and qualified imports).  For example, it really does not seem that
inconvenient (and, in fact, I find it helpful!) to write the following:

import Data.List hiding (foldr)
import Data.Foldable

Last, but not least, in my experience being explicit about the dependencies
of a module (i.e., using implicit import lists and qualified imports) tends
to lead to (i) more robust code because it reduces accidental breakage due
to new versions of libraries, and (ii) more readable code, because it makes
it easier to follow the code dependencies, which is especially important
when studying a new large code base.

-Iavor
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-25 Thread Daniel Gorín
> Oh my!  Now it's getting complicated.  

Hopefully not so!

> * I suppose that if Data.List re-exports foldr, it would go with the more 
> specific type.  

Yes.

> * In your example, can I also use the more-polymorphic foldr, perhaps by 
> saying Data.Foldable.foldr?

Yes. More precisely, if you import both Data.List and Data.Foldable and try to 
use foldr, it will have the more general type that comes from Data.Foldable.

> * I wonder what would happen if Data.Foo specialised foldr in a different 
> way, and some module imported both Data.List and Data.Foo.  Maybe it would be 
> ok if one of the two specialised types was more specific than the other but 
> not if they were comparable?

Right, that is what I was proposing. If the specialization of foldr in 
Data.List is more general than the one in Data.Foo, the former is used. If the 
converse is the case, the latter is used. If none is more general, the module 
cannot be compiled. The solution in this case is to import also Data.Foldable, 
which provides a version of foldr that is more general than the ones in 
Data.List and Data.Foo.

> * What happens for classes?  Can you specialise the signatures there?  And 
> make instances of that specialised class?

No; I don't think that would be sound. The proposal was to extend the grammar 
for export lists allowing type signatures for qvars only.

> * Ditto data types

Datatypes are not covered by the proposal either.

> It feel a bit like a black hole to me.

As it is, the proposal should affect only the module system, where it is 
determined what the type of an imported symbol is. In particular, the 
typechecker would go unaware of it. In that sense, I see the proposal as a very 
mild extension.

Thanks,
Daniel.



> Simon
> | -Original Message-
> | From: Daniel Gorín [mailto:dgo...@dc.uba.ar]
> | Sent: 24 May 2013 08:42
> | To: Simon Peyton-Jones
> | Cc: glasgow-haskell-users@haskell.org
> | Subject: Re: A language extension for dealing with Prelude.foldr vs
> | Foldable.foldr and similar dilemmas
> | 
> | On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
> | 
> | > How about (in Haskell98)
> | >
> | >   module Data.List ( foldr, ...)
> | >   import qualified Data.Foldable
> | >   foldr :: (a -> b -> b) -> b -> [a] -> b
> | >   foldr = Data.Foldable.foldr
> | 
> | It would not be the same! Using your example one will get that the following
> | fails to compile:
> | 
> | > import Data.List
> | > import Data.Foldable
> | > f = foldr
> | 
> | The problem is that Data.List.foldr and Data.Foldable.foldr are here 
> different
> | symbols with the same name.
> | This is precisely why Foldable, Traversable, Category, etc are awkward to 
> use.
> | The proposal is to make Data.List reexport Data.Foldable.foldr (with a more
> | specialized type) so that the module above can be accepted.
> | 
> | Thanks,
> | Daniel
> | 
> | > Simon
> | >
> | > | -Original Message-
> | > | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
> | > | users-boun...@haskell.org] On Behalf Of Daniel Gorín
> | > | Sent: 24 May 2013 01:27
> | > | To: glasgow-haskell-users@haskell.org
> | > | Subject: A language extension for dealing with Prelude.foldr vs
> | Foldable.foldr
> | > | and similar dilemmas
> | > |
> | > | Hi all,
> | > |
> | > | Given the ongoing discussion in the libraries mailing list on replacing 
> (or
> | > | removing) list functions in the Prelude in favor of the Foldable / 
> Traversable
> | > | generalizations, I was wondering if this wouldn't be better handled by a
> | mild
> | > | (IMO) extension to the module system.
> | > |
> | > | In a nutshell, the idea would be 1) to allow a module to export a 
> specialized
> | > | version of a symbol (e.g., Prelude could export Foldable.foldr but with 
> the
> | > | specialized type (a -> b -> b) -> b -> [a] -> b) and 2) provide a
> | disambiguation
> | > | mechanism by which when a module imports several versions of the same
> | > | symbol (each, perhaps, specialized), a sufficiently general type is 
> assigned
> | to it.
> | > |
> | > | The attractive I see in this approach is that (enabling an extension) 
> one
> | could
> | > | just import and use Foldable and Traversable (and even Category!) 
> without
> | > | qualifying nor hiding anything; plus no existing code would break and
> | beginners
> | > | would still get  the friendlier error of the monomorphic functions. I 
> also
> | expect
> | > | it to be relatively easy to implement.
> | > |
> | > | In more detail, the proposal

RE: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-24 Thread Simon Peyton-Jones
Oh my!  Now it's getting complicated.  
* I suppose that if Data.List re-exports foldr, it would go with the more 
specific type.  
* In your example, can I also use the more-polymorphic foldr, perhaps by saying 
Data.Foldable.foldr?
* I wonder what would happen if Data.Foo specialised foldr in a different way, 
and some module imported both Data.List and Data.Foo.  Maybe it would be ok if 
one of the two specialised types was more specific than the other but not if 
they were comparable?
* What happens for classes?  Can you specialise the signatures there?  And make 
instances of that specialised class?
* Ditto data types

It feel a bit like a black hole to me.

Simon
| -Original Message-
| From: Daniel Gorín [mailto:dgo...@dc.uba.ar]
| Sent: 24 May 2013 08:42
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: A language extension for dealing with Prelude.foldr vs
| Foldable.foldr and similar dilemmas
| 
| On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:
| 
| > How about (in Haskell98)
| >
| > module Data.List ( foldr, ...)
| > import qualified Data.Foldable
| > foldr :: (a -> b -> b) -> b -> [a] -> b
| > foldr = Data.Foldable.foldr
| 
| It would not be the same! Using your example one will get that the following
| fails to compile:
| 
| > import Data.List
| > import Data.Foldable
| > f = foldr
| 
| The problem is that Data.List.foldr and Data.Foldable.foldr are here different
| symbols with the same name.
| This is precisely why Foldable, Traversable, Category, etc are awkward to use.
| The proposal is to make Data.List reexport Data.Foldable.foldr (with a more
| specialized type) so that the module above can be accepted.
| 
| Thanks,
| Daniel
| 
| > Simon
| >
| > | -Original Message-
| > | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| > | users-boun...@haskell.org] On Behalf Of Daniel Gorín
| > | Sent: 24 May 2013 01:27
| > | To: glasgow-haskell-users@haskell.org
| > | Subject: A language extension for dealing with Prelude.foldr vs
| Foldable.foldr
| > | and similar dilemmas
| > |
| > | Hi all,
| > |
| > | Given the ongoing discussion in the libraries mailing list on replacing 
(or
| > | removing) list functions in the Prelude in favor of the Foldable / 
Traversable
| > | generalizations, I was wondering if this wouldn't be better handled by a
| mild
| > | (IMO) extension to the module system.
| > |
| > | In a nutshell, the idea would be 1) to allow a module to export a 
specialized
| > | version of a symbol (e.g., Prelude could export Foldable.foldr but with 
the
| > | specialized type (a -> b -> b) -> b -> [a] -> b) and 2) provide a
| disambiguation
| > | mechanism by which when a module imports several versions of the same
| > | symbol (each, perhaps, specialized), a sufficiently general type is 
assigned
| to it.
| > |
| > | The attractive I see in this approach is that (enabling an extension) one
| could
| > | just import and use Foldable and Traversable (and even Category!) without
| > | qualifying nor hiding anything; plus no existing code would break and
| beginners
| > | would still get  the friendlier error of the monomorphic functions. I also
| expect
| > | it to be relatively easy to implement.
| > |
| > | In more detail, the proposal is to add two related language extensions,
| which,
| > | for the sake of having a name, I refer to here as MoreSpecificExports and
| > | MoreGeneralImports.
| > |
| > | 1) With MoreSpecificExports the grammar is extended to allow type
| > | annotations on symbols in the export list of a module. One could then 
have,
| > | e.g., something like:
| > |
| > | {-# LANGUAGE MoreSpecificExports #-}
| > | module Data.List (
| > |  ...
| > |  Data.Foldable.foldr :: (a -> b -> b) -> b -> [a] -> b
| > |, Data.Foldable.foldl :: (b -> a -> b) -> b -> [a] -> b
| > | ...
| > | )
| > |
| > | where
| > |
| > | import Data.Foldable
| > | ...
| > |
| > | instance Foldable [] where ...
| > |
| > |
| > | For consistency, symbols defined in the module could also be exported
| > | specialized. The type-checker needs to check that the type annotation is 
in
| fact
| > | a valid specialization of the original type, but this is, I think, 
straightforward.
| > |
| > |
| > | 2) If a module imports Data.List and Data.Foldable as defined above
| *without*
| > | the counterpart MoreGeneralImports extension, then Data.List.foldr and
| > | Data.Foldable.foldr are to be treated as unrelated symbols, so foldr would
| be
| > | an ambiguous symbol, just like it is now.
| > |
| > | If on the other hand a module enables MoreGeneralImports and a symbol f
| is
| > | imported n times with types T1, T2, 

Re: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-24 Thread Daniel Gorín
On May 24, 2013, at 9:28 AM, Simon Peyton-Jones wrote:

> How about (in Haskell98)
> 
>   module Data.List ( foldr, ...)
>   import qualified Data.Foldable
>   foldr :: (a -> b -> b) -> b -> [a] -> b
>   foldr = Data.Foldable.foldr

It would not be the same! Using your example one will get that the following 
fails to compile:

> import Data.List
> import Data.Foldable
> f = foldr

The problem is that Data.List.foldr and Data.Foldable.foldr are here different 
symbols with the same name. 
This is precisely why Foldable, Traversable, Category, etc are awkward to use. 
The proposal is to make Data.List reexport Data.Foldable.foldr (with a more 
specialized type) so that the module above can be accepted.

Thanks,
Daniel 

> Simon
> 
> | -Original Message-
> | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
> | users-boun...@haskell.org] On Behalf Of Daniel Gorín
> | Sent: 24 May 2013 01:27
> | To: glasgow-haskell-users@haskell.org
> | Subject: A language extension for dealing with Prelude.foldr vs 
> Foldable.foldr
> | and similar dilemmas
> | 
> | Hi all,
> | 
> | Given the ongoing discussion in the libraries mailing list on replacing (or
> | removing) list functions in the Prelude in favor of the Foldable / 
> Traversable
> | generalizations, I was wondering if this wouldn't be better handled by a 
> mild
> | (IMO) extension to the module system.
> | 
> | In a nutshell, the idea would be 1) to allow a module to export a 
> specialized
> | version of a symbol (e.g., Prelude could export Foldable.foldr but with the
> | specialized type (a -> b -> b) -> b -> [a] -> b) and 2) provide a 
> disambiguation
> | mechanism by which when a module imports several versions of the same
> | symbol (each, perhaps, specialized), a sufficiently general type is 
> assigned to it.
> | 
> | The attractive I see in this approach is that (enabling an extension) one 
> could
> | just import and use Foldable and Traversable (and even Category!) without
> | qualifying nor hiding anything; plus no existing code would break and 
> beginners
> | would still get  the friendlier error of the monomorphic functions. I also 
> expect
> | it to be relatively easy to implement.
> | 
> | In more detail, the proposal is to add two related language extensions, 
> which,
> | for the sake of having a name, I refer to here as MoreSpecificExports and
> | MoreGeneralImports.
> | 
> | 1) With MoreSpecificExports the grammar is extended to allow type
> | annotations on symbols in the export list of a module. One could then have,
> | e.g., something like:
> | 
> | {-# LANGUAGE MoreSpecificExports #-}
> | module Data.List (
> |  ...
> |  Data.Foldable.foldr :: (a -> b -> b) -> b -> [a] -> b
> |, Data.Foldable.foldl :: (b -> a -> b) -> b -> [a] -> b
> | ...
> | )
> | 
> | where
> | 
> | import Data.Foldable
> | ...
> | 
> | instance Foldable [] where ...
> | 
> | 
> | For consistency, symbols defined in the module could also be exported
> | specialized. The type-checker needs to check that the type annotation is in 
> fact
> | a valid specialization of the original type, but this is, I think, 
> straightforward.
> | 
> | 
> | 2) If a module imports Data.List and Data.Foldable as defined above 
> *without*
> | the counterpart MoreGeneralImports extension, then Data.List.foldr and
> | Data.Foldable.foldr are to be treated as unrelated symbols, so foldr would 
> be
> | an ambiguous symbol, just like it is now.
> | 
> | If on the other hand a module enables MoreGeneralImports and a symbol f is
> | imported n times with types T1, T2, ... Tn,  the proposal is to assign to f 
> the
> | most general type among T1... Tn, if such type exists (or fail otherwise). 
> So if in
> | the example above we enable MoreGeneralImports, foldr will have type
> | Foldable t => (a -> b -> b) -> b -> t a -> b, as desired.
> | 
> | (It could be much more interesting to assign to f the least general
> | generalization of T1...Tn, but this seems to require much more work (unless
> | GHC already implements some anti-unification algorithm); also I'm not sure
> | whether this would interact well with GADTs or similar features and in any 
> case
> | this could be added at a later stage without breaking existing programs).
> | 
> | 
> | Would something like this address the problem? Are there any interactions 
> that
> | make this approach unsound? Any obvious cons I'm not seeing? Feedback is
> | most welcome!
> | 
> | Thanks,
> | Daniel
> | ___
> | Glasgow-haskell-users mailing list
> | Glasgow-haskell-users@haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-24 Thread Simon Peyton-Jones
How about (in Haskell98)

module Data.List ( foldr, ...)
import qualified Data.Foldable
foldr :: (a -> b -> b) -> b -> [a] -> b
foldr = Data.Foldable.foldr

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Daniel Gorín
| Sent: 24 May 2013 01:27
| To: glasgow-haskell-users@haskell.org
| Subject: A language extension for dealing with Prelude.foldr vs Foldable.foldr
| and similar dilemmas
| 
| Hi all,
| 
| Given the ongoing discussion in the libraries mailing list on replacing (or
| removing) list functions in the Prelude in favor of the Foldable / Traversable
| generalizations, I was wondering if this wouldn't be better handled by a mild
| (IMO) extension to the module system.
| 
| In a nutshell, the idea would be 1) to allow a module to export a specialized
| version of a symbol (e.g., Prelude could export Foldable.foldr but with the
| specialized type (a -> b -> b) -> b -> [a] -> b) and 2) provide a 
disambiguation
| mechanism by which when a module imports several versions of the same
| symbol (each, perhaps, specialized), a sufficiently general type is assigned 
to it.
| 
| The attractive I see in this approach is that (enabling an extension) one 
could
| just import and use Foldable and Traversable (and even Category!) without
| qualifying nor hiding anything; plus no existing code would break and 
beginners
| would still get  the friendlier error of the monomorphic functions. I also 
expect
| it to be relatively easy to implement.
| 
| In more detail, the proposal is to add two related language extensions, which,
| for the sake of having a name, I refer to here as MoreSpecificExports and
| MoreGeneralImports.
| 
| 1) With MoreSpecificExports the grammar is extended to allow type
| annotations on symbols in the export list of a module. One could then have,
| e.g., something like:
| 
| {-# LANGUAGE MoreSpecificExports #-}
| module Data.List (
|  ...
|  Data.Foldable.foldr :: (a -> b -> b) -> b -> [a] -> b
|, Data.Foldable.foldl :: (b -> a -> b) -> b -> [a] -> b
| ...
| )
| 
| where
| 
| import Data.Foldable
| ...
| 
| instance Foldable [] where ...
| 
| 
| For consistency, symbols defined in the module could also be exported
| specialized. The type-checker needs to check that the type annotation is in 
fact
| a valid specialization of the original type, but this is, I think, 
straightforward.
| 
| 
| 2) If a module imports Data.List and Data.Foldable as defined above *without*
| the counterpart MoreGeneralImports extension, then Data.List.foldr and
| Data.Foldable.foldr are to be treated as unrelated symbols, so foldr would be
| an ambiguous symbol, just like it is now.
| 
| If on the other hand a module enables MoreGeneralImports and a symbol f is
| imported n times with types T1, T2, ... Tn,  the proposal is to assign to f 
the
| most general type among T1... Tn, if such type exists (or fail otherwise). So 
if in
| the example above we enable MoreGeneralImports, foldr will have type
| Foldable t => (a -> b -> b) -> b -> t a -> b, as desired.
| 
| (It could be much more interesting to assign to f the least general
| generalization of T1...Tn, but this seems to require much more work (unless
| GHC already implements some anti-unification algorithm); also I'm not sure
| whether this would interact well with GADTs or similar features and in any 
case
| this could be added at a later stage without breaking existing programs).
| 
| 
| Would something like this address the problem? Are there any interactions that
| make this approach unsound? Any obvious cons I'm not seeing? Feedback is
| most welcome!
| 
| Thanks,
| Daniel
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


A language extension for dealing with Prelude.foldr vs Foldable.foldr and similar dilemmas

2013-05-23 Thread Daniel Gorín
Hi all,

Given the ongoing discussion in the libraries mailing list on replacing (or 
removing) list functions in the Prelude in favor of the Foldable / Traversable 
generalizations, I was wondering if this wouldn't be better handled by a mild 
(IMO) extension to the module system. 

In a nutshell, the idea would be 1) to allow a module to export a specialized 
version of a symbol (e.g., Prelude could export Foldable.foldr but with the 
specialized type (a -> b -> b) -> b -> [a] -> b) and 2) provide a 
disambiguation mechanism by which when a module imports several versions of the 
same symbol (each, perhaps, specialized), a sufficiently general type is 
assigned to it.

The attractive I see in this approach is that (enabling an extension) one could 
just import and use Foldable and Traversable (and even Category!) without 
qualifying nor hiding anything; plus no existing code would break and beginners 
would still get  the friendlier error of the monomorphic functions. I also 
expect it to be relatively easy to implement.

In more detail, the proposal is to add two related language extensions, which, 
for the sake of having a name, I refer to here as MoreSpecificExports and 
MoreGeneralImports.

1) With MoreSpecificExports the grammar is extended to allow type annotations 
on symbols in the export list of a module. One could then have, e.g., something 
like:

{-# LANGUAGE MoreSpecificExports #-}
module Data.List (
 ...
 Data.Foldable.foldr :: (a -> b -> b) -> b -> [a] -> b
   , Data.Foldable.foldl :: (b -> a -> b) -> b -> [a] -> b
...
)

where

import Data.Foldable
...

instance Foldable [] where ...


For consistency, symbols defined in the module could also be exported 
specialized. The type-checker needs to check that the type annotation is in 
fact a valid specialization of the original type, but this is, I think, 
straightforward.


2) If a module imports Data.List and Data.Foldable as defined above *without* 
the counterpart MoreGeneralImports extension, then Data.List.foldr and 
Data.Foldable.foldr are to be treated as unrelated symbols, so foldr would be 
an ambiguous symbol, just like it is now.

If on the other hand a module enables MoreGeneralImports and a symbol f is 
imported n times with types T1, T2, ... Tn,  the proposal is to assign to f the 
most general type among T1... Tn, if such type exists (or fail otherwise). So 
if in the example above we enable MoreGeneralImports, foldr will have type 
Foldable t => (a -> b -> b) -> b -> t a -> b, as desired.

(It could be much more interesting to assign to f the least general 
generalization of T1...Tn, but this seems to require much more work (unless GHC 
already implements some anti-unification algorithm); also I'm not sure whether 
this would interact well with GADTs or similar features and in any case this 
could be added at a later stage without breaking existing programs).


Would something like this address the problem? Are there any interactions that 
make this approach unsound? Any obvious cons I'm not seeing? Feedback is most 
welcome!

Thanks,
Daniel
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users