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

Daniel Gorín dgorin at dc.uba.ar
Fri May 24 09:42:29 CEST 2013


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-bounces at haskell.org [mailto:glasgow-haskell-
> | users-bounces at haskell.org] On Behalf Of Daniel Gorín
> | Sent: 24 May 2013 01:27
> | To: glasgow-haskell-users at 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 at haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list