[Haskell-cafe] language proposal: ad-hoc overloading
Claus Reinke
claus.reinke at talk21.com
Sun Aug 31 17:10:52 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.
Indeed. Too much overloading can be a lot of trouble.
You can do adhoc overloading already:
{-# LANGUAGE FlexibleInstances #-}
class Adhoc a where adhoc :: a
instance Adhoc ((a->b)->([a]->[b])) where adhoc = map
instance Adhoc (Maybe a->a) where adhoc = maybe (error "wrong number") id
instance Adhoc [Char] where adhoc = "hello, world"
instance Adhoc (String->IO ()) where adhoc = print
main :: IO ()
main = adhoc (adhoc (adhoc . Just :: Char -> Char) (adhoc :: String) :: String)
I hope this also demonstrates why it is usually a bad idea, even if
it often looks good in theory. If you're not convinced yet, play with
this kind of code in practice.
The "well-typed programs don't go wrong" of static type checking
depends on a clear separation of "right" and "wrong". If your use of
types allows anything to be a valid program, minor variations in code
will no longer be caught by the type system: at best, you'll get "missing
instance", more likely you'll get "too many possibilities", and at worst,
the code will simply do something different.
> What CAN be useful is, IMHO, to make your IDE substitute this "M."s
> for you when you type.
haskellmode for Vim does that (though it isn't type aware, so you
get a larger menu of possible completions than necessary).
Claus
[1] http://www.cs.kent.ac.uk/~cr3/toolbox/haskell/Vim/
More information about the Haskell-Cafe
mailing list