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

Ryan Ingram ryani.spam at gmail.com
Sun Aug 31 14:21:44 EDT 2008


The point of having a strongly typed language is so the compiler can
do more work for you.  But right now I do a lot of typing (pun not
intended) to appease the compiler.

Let me give you an example:

module Prob where
import qualified Data.Map as M
...

newtype Prob p a = Prob { runProb :: [(a,p)] }

combine :: (Num p, Ord a) => Prob p a -> Prob p a
combine m = Prob $
    M.assocs $
    foldl' (flip $ uncurry $ M.insertWith (+)) M.empty $
    runProb m

Do you see it?  All those "M." just seem dirty to me, especially
because the compiler should be able to deduce them from the types of
the arguments.

My proposal is to allow "ad-hoc" overloading of names; if a name is
ambiguous in a scope, attempt to type-check the expression against
each name.  It is only an error if type-checking against all names
fails.  If type-checking succeeds for more than one then the
expression is ambiguous and this is also an error.

Pros: shorter code, less busywork to please the compiler
Cons: potentially exponential compile time?

Any thoughts?

  -- ryan


More information about the Haskell-Cafe mailing list