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

Ryan Ingram ryani.spam at gmail.com
Sun Aug 31 19:08:48 EDT 2008


On Sun, Aug 31, 2008 at 2:10 PM, Claus Reinke <claus.reinke at talk21.com> wrote:
> 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

Yes, of course taken to this extent it is bad, but I'm not suggesting
this at all.  In particular, we have well-chosen names for many
functions, but not every container can use exact same interface (see,
for example, the many discussions on "restricted monads").  So we
can't reuse the same function name for similar concepts that have
slightly different interfaces.

>   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.

I do play with this kind of code in practice, in other languages.  In
practice, I don't see the kind of problems you are bringing up occur.
However, those languages tend to be dynamically typed so I do get the
occasional runtime type error.

I'd much rather have a safe way of doing less typing than an unsafe way.

As an example of this done correctly, in Ruby, you have
Array#each:
   [1,2,3].each { |x| print x }
Hash#each:
   { :foo => "hello", :bar => "world" }.each { |k, v| print v }
etc.

"each" corresponds to the idea of iterating over a container (foldM in
Haskell) without being a slave to maintaining an identical API for
each type.

I maintain that in Haskell, trying to get this same generality often
leads to abuse of the typeclass system for things where the types
should trivially be determined at compile time.

> 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.

I don't think this is a strong argument.  In practice most things have
a single concrete type and helping the compiler with extra qualified
names is just meaningless typing.

I'm suggesting that in the case of this code:
> import Data.Map as M
> x = map (+1) M.empty
"map" should be inferred as "M.map" instead of being ambiguous.

There's already some minor work in the direction I am suggesting in
record syntax, but it only works during pattern matching.  I'd like
"cx foo + cy foo" to work on any "foo" that has record members cx and
cy that are members of Num, instead of needing to preface every record
with the datatype name to avoid ambiguity.

In particular I do NOT want each function in its own typeclass; the
previous post saying:
> foo x = map (bar x)
should be rejected as ambiguous without a type signature somewhere (at
least, if Data.Map is imported).  This does give some amount of
"action at a distance" where changing a file that is imported by
another file can cause previously unambiguous code to become
ambiguous, but that is already true!  And this modification would make
it less likely to be the case.

As to the argument that a "sufficiently smart IDE" would insert the
"M." for me, I think that is flawed.  First, there isn't a
sufficiently smart IDE yet, and second, it'd be better for the
type-aware IDE to tell me the types of things when I (for example)
mouse over them, instead of helping me type longer things.

  -- ryan


More information about the Haskell-Cafe mailing list