[Haskell-cafe] language proposal: ad-hoc overloading
Daniel Fischer
daniel.is.fischer at web.de
Sun Aug 31 14:58:37 EDT 2008
Am Sonntag, 31. August 2008 20:21 schrieb Ryan Ingram:
> 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
Another Con is that the compiler can catch fewer programming errors that way.
I can't think of a credible example right now, but what if you typo'd a
function argument, it typechecks according to the above rules, but with a
completely unintended function and your programme outputs garbage (of course,
garbage which is not immediately recognisable as such)?
Still, I often have the same desire when I forget a qualification :)
Cheers,
Daniel
More information about the Haskell-Cafe
mailing list