[Haskell-cafe] Type classes vr.s functions

Luke Palmer lrpalmer at gmail.com
Sun Dec 21 01:08:21 EST 2008


On Sat, Dec 20, 2008 at 6:20 PM, Brian Hurt <bhurt at spnz.org> wrote:

>
> So, style question for people, if I can.  I have a certain problem-
> basically, I have a bunch of functions which need a special function,
> of type a -> Foo say.  And a bunch of other functions which can define
> that function on some type of interest, and then what to call the first
> batch of functions.  I can do this either by defining a type class,
> something like:
> class Fooable a where
>    toFoo :: a -> Foo
> or I can simply have all the functions which need a toFoo take an extra
> agrument.  Performance really isn't that important here, so it's really
> a matter of style- which approach would people prefer in this case?


And it doesn't matter as the performance would be the same in the two cases
also.

My general rule of thumb is to always write combinators first, since they do
not suffer the composability limitations that typeclasses do (rougly
typeclasses perform a proof search which is subject to restrictions to
ensure decidability, whereas with combinators you provide the proof, so
there are no such restrictions).  Then typeclass instances can be trivially
defined in terms of the combinators.  Note that the other way around is not
usually possible.  So eg.:

  module Foo where

  type Fooify a = a -> Foo
  int :: Fooify Int
  int = ...
  list :: Fooify a -> Fooify [a]
  list = ...

  -- then, if determined that this would be convenient
  class Fooable a where
      toFoo :: Fooify a

  instance Fooable Int where toFoo = int
  instance (Fooable a) => Fooable [a] where toFoo = list toFoo
  ...

Luke


>
> Brian
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20081220/c91ef566/attachment.htm


More information about the Haskell-Cafe mailing list