
On Mon, 2008-10-13 at 19:51 +0100, Andrew Coppin wrote:
{-# LANGUAGE FlexibleInstances #-}
module Overload where
class Silly s where go :: s
instance Silly ([x] -> [x]) where go = reverse
instance Silly (Int -> Int) where go = (+1)
Don't even ask.
Suffice it to say, you *can* make Haskell support arbitrary overloading of function names like C++ has, _if_ you abuse the type system violently enough. Please, won't somebody think of the children?!?
Flexible instances are extroardinarily useful: instance Monad m => MonadState s (StateT s m) instance MonadState t m => MonadState (s, t) (StateT s m) is a useful and not entirely insane instance scheme. But yeah, anyone who uses class Silly in real life should be banned from coming within a 100 feet of any place where math, science, engineering, or software development is carried out or taught. I don't know if it's necessary for the good of the Children, but we need to start thinking of the poor, defenseless computers as well... jcc