[Haskell-cafe] language proposal: ad-hoc overloading

Ryan Ingram ryani.spam at gmail.com
Sun Aug 31 22:14:47 EDT 2008


On Sun, Aug 31, 2008 at 5:11 PM, David House <dmhouse at gmail.com> wrote:
> Here's an example of such a concern: you write the following:

> module Amb where
> import Data.Map
>
> foo = map

> What is the type of `foo'?

Exactly the same as now: it has no type:

amb.hs:4:6:
    Ambiguous occurrence `map'
    It could refer to either `Prelude.map', imported from Prelude
                          or `Data.Map.map', imported from Data.Map at
amb.hs:2:0-14

On the other hand, this module would no longer fail to compile:

> module Amb where
> import Data.Map
>
> foo :: (a -> b) -> [a] -> [b]
> foo = map

which right now gives the same error message as above, but with my
proposal would successfully compile, with foo = Prelude.map.

As Philippa said, the naive implementation is:

1) Attempt to typecheck with all permutations of ambiguous names
2a) If zero permutations typecheck, type error.
2b) If multiple permutations typecheck, the program is ambiguous
(current behavior)
2c) Otherwise, exactly one typechecks successfully.  Specialize the
ambiguous names to the chose permutation and continue compilation.

It is a conservative extension of the language, because any program
that successfully compiles now has no change: there are no ambiguous
names in any currently compiling Haskell program.  But it accepts some
additional programs that have ambiguities, by choosing the only result
that typechecks.  If there is more than one possible type for foo, the
program is still ambiguous and therefore should not compile.

  -- ryan


More information about the Haskell-Cafe mailing list