[Haskell-cafe] I hate Haskell's typeclasses

Ryan Ingram ryani.spam at gmail.com
Tue Apr 22 12:53:57 EDT 2008


On Mon, Apr 21, 2008 at 10:58 PM, Jonathan Cast
<jonathanccast at fastmail.fm> wrote:
>  I must have failed to communicate well.  To me, the point of giving a class
> a name is that then you can write a program that is parametric over the
> elements of that class.  Knowing that I can implement monads in Ruby doesn't
> impress me nearly as much as knowing that I can implement mapM does.
> Haskell has me addicted to code reuse (mapM) the way the rest of the
> programming world is addicted to design patterns (monads).  What I mean by
> `encoding Num and Monad' is that you can do something like this:
>
>  sum = foldr (+) 0
>  sequence = foldr (liftM2 (:)) (return [])
>
>  I don't know of any language that is dynamically typed and also can encode
> `return' or `0' in a way that lets those examples work.  Statically typed
> languages where it works are rare, even.  Haskell gives up a fair amount of
> control by making these things implicit, which is what I think you're
> running up against --- but I think it gets something useful and non-trivial
> to acheive in return.

I think ruby generally solves this problem via duck-typing; instead of
the cast happening in the (implicit) fromInteger call in sum above,
instead the cast happens in the function with more information via a
call to otherclass#to_whatever_i_am.  You can do something like this:

class Frob
   attr_reader :val
   def initialize(i)
       @val = i
   end
   def to_frob
      self
   end
   def +(rhs)
      rhsF = rhs.to_frob
      Frob.new(rhsF.val + @val)
   end
end

class Integer
   def to_frob
       Frob.new(self)
   end
end

class Array
   def sum
       foldl(0) {|acc,x| acc + x}
   end
   def foldl(z)
      each {|x| z = yield(z,x)}
      z
   end
end

irb(main):055:0> [1,2,3].sum
=> 6
irb(main):057:0> [1,2,3].map {|x| Frob.new(x)}.sum
=> #<Frob:0x2b65cf0 @val=6>

>  I'll agree with this point.  I've complained, concretely, about the lack of
> instances for (some) standard types before.  (STM is actually a rather bad
> offender here; it's lacking MonadPlus, as well, despite the specific
> observation in the paper that it has the right signature for that class.)

Actually:

GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
Prelude> :m Control.Monad Control.Monad.STM
Prelude Control.Monad.STM Control.Monad> :i STM
...
instance MonadPlus STM -- Defined in Control.Monad.STM

>  When can we discharge a MaybeInstance context?

On any concrete type.  Like Typeable should be :)
The compiler then determines whether that type is an instance of the
class and provides the appropriate dictionary if applicable.

>  Having the | Show a test suddenly trip from False to True because some
> other module imported Text.Show.Functions sounds like an odd change to me.
> At any rate, it scares me enough to make me oppose the idea.

I see the worry now.  I think this is more of a problem with orphan
instances; are orphan instances considered to be a valuable enough
feature to avoid potentially more powerful constructs?

Maybe there is a better solution to the "I have class C from library X
and type T from library Y and I want to make them play nice together"
problem than orphan instances.

>  class Forceable alpha where
>   seq :: alpha -> beta -> beta
>
>  Instances derived automatically by the compiler, when possible, for every
> type (like Typeable should be).  We can omit functions if desired (I don't
> remember why I thought this was a good idea).  When you say
>
>  f :: alpha -> beta
>
>  or
>
>  f :: C alpha => alpha -> beta
>
>  The compiler adds implicit Forceable constraints on alpha and beta.  But,
> if you say
>
>  f :: !Forceable alpha => alpha -> beta
>
>  The compiler leaves the Forceable alpha constraint off.  Then you can say
>
>  build :: (forall c. !Forceable c => (a -> c -> c) -> c -> c) -> [a]
>
>  And the foldr/build law is still sound.

This seems like a really interesting idea.

  -- ryan


More information about the Haskell-Cafe mailing list