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

Miguel Mitrofanov miguelimo38 at yandex.ru
Sun Aug 31 16:01:30 EDT 2008


Well, I was thinking that way when I was starting learning Haskell.  
But then I realized that this "feature" would make code much harder to  
read. Suppose you have different thing all named "insertWith". You've  
got one somewhere in your program; how do YOU know when looking at the  
code after a month or so, which one is this? Certainly, given a smart  
IDE you can ask it; but I think that code should be clear just when  
you look at it, without any action.

What CAN be useful is, IMHO, to make your IDE substitute this "M."s  
for you when you type.

On 31 Aug 2008, at 22:21, Ryan Ingram wrote:

> 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
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list