
Dan Weston wrote:
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. Dynamic dispatch is easily added to Haskell code by using an existential to represent any collision:
{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-} module Collide where -- Changed to a single param to make life easier... class Collide a where collide :: a -> 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) -- This is how you get dynamic dispatch in Haskell data Collision = forall a. Collide a => Collision a instance Collide Collision where collide (Collision a) = collide a -- ghci output *Collide> let ae = Collision (Asteroid, Earth) *Collide> let pa = Collision (Planet, Asteroid) *Collide> collide ae "the end of the dinos" *Collide> collide pa "an asteroid hit a planet" *Collide> map collide [ae, pa] ["the end of the dinos","an asteroid hit a planet"] Best regards, Brian.