[Haskell-cafe] Newbie question: "multi-methods" in Haskell

Dan Weston westondan at imageworks.com
Mon Aug 6 14:37:17 EDT 2007


Remember that type classes do not provide object-oriented functionality.=20
The dispatch is static, not dynamic. Although OOP can be simulated in=20
Haskell, it is not a natural idiom. If you need dynamic dispatch=20
(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 =93multi-methods=94
>=20
>> Using multi-methods, I could write (in pseudo code)
>> collide (Asteroid, Planet) =3D "an asteroid hit a planet"
>> collide (Asteroid, Earth) =3D "the end of the dinos"
>> ...
>> collide (Planet, Asteroid) =3D collide (Asteroid, Planet)
>> collide (Earth, Asteroid)  =3D collide (Earth, Asteroid)
>=20
> Hi, In Haskell you can use multi parameter type classes to solve this=20
> problem:
>=20
> {-# OPTIONS_GHC -fglasgow-exts
>        -fallow-undecidable-instances
>        -fallow-overlapping-instances #-}
>=20
> module Collide where
>=20
> class Collide a b where
>    collide :: (a,b) -> String
>=20
> data Solid =3D Solid
> data Asteroid =3D Asteroid
> data Planet =3D Planet
> data Jupiter =3D Jupiter
> data Earth =3D Earth
>=20
> instance Collide Asteroid Planet where
>    collide (Asteroid, Planet) =3D "an asteroid hit a planet"
>=20
> instance Collide Asteroid Earth where
>    collide (Asteroid, Earth) =3D "the end of the dinos"
>=20
> -- Needs overlapping and undecidable instances
> instance Collide a b =3D> Collide b a where
>    collide (a,b) =3D collide (b, a)
>=20
> -- ghci output
> *Collide> collide (Asteroid, Earth)
> "the end of the dinos"
> *Collide> collide (Earth, Asteroid)
> "the end of the dinos"
>=20
> Best regards, Brian.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>=20
>=20




More information about the Haskell-Cafe mailing list