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

Gwern Branwen gwern0 at gmail.com
Sun Aug 31 16:43:28 EDT 2008


On 2008.08.31 11:21:44 -0700, Ryan Ingram <ryani.spam at gmail.com> scribbled 1.0K characters:
> 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

I think this would be very nice in GHCi, because there the situation is even *worse*.

I think we've all experienced importing Data.Map or Data.ByteString and discovering we need to tediously write it out in *full*, because we can't even do qualified imports of it!

--
gwern
BND fritz FKS 1071 Face government Tomahawk DREO IA O
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 197 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20080831/dd0c959a/attachment.bin


More information about the Haskell-Cafe mailing list