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

Reply via email to