
Remember that type classes do not provide object-oriented functionality. The dispatch is static, not dynamic. Although OOP can be simulated in Haskell, it is not a natural idiom. If you need dynamic dispatch (including multiple dispatch), you may want to reconsider your solution. Dan Weston Brian Hulley wrote:
peterv wrote:
In de book Modern C++ design, Andrei Alexandrescu writes that Haskell supports “multi-methods”
Using multi-methods, I could write (in pseudo code) collide (Asteroid, Planet) = "an asteroid hit a planet" collide (Asteroid, Earth) = "the end of the dinos" ... collide (Planet, Asteroid) = collide (Asteroid, Planet) collide (Earth, Asteroid) = collide (Earth, Asteroid)
Hi, In Haskell you can use multi parameter type classes to solve this problem:
{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-}
module Collide where
class Collide a b where collide :: (a,b) -> String
data Solid = Solid data Asteroid = Asteroid data Planet = Planet data Jupiter = Jupiter data Earth = Earth
instance Collide Asteroid Planet where collide (Asteroid, Planet) = "an asteroid hit a planet"
instance Collide Asteroid Earth where collide (Asteroid, Earth) = "the end of the dinos"
-- Needs overlapping and undecidable instances instance Collide a b => Collide b a where collide (a,b) = collide (b, a)
-- ghci output *Collide> collide (Asteroid, Earth) "the end of the dinos" *Collide> collide (Earth, Asteroid) "the end of the dinos"
Best regards, Brian. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe