Newbie question: "multi-methods" in Haskell

In de book Modern C++ design, Andrei Alexandrescu writes that Haskell supports “multi-methods” http://books.google.com/books?id=aJ1av7UFBPwC&pg=PA3&ots=YPiJ_nWi6Y&dq=moder n+C%2B%2B&sig=FWO6SVfIrgtCWifj9yYHj3bnplQ#PPA263,M1 How is this actually done in Haskell? Maybe this is just a basic feature of Haskell which I don't grasp yet because of my object-oriented background? A good example is collision between pairs of objects of type (a,b). In object oriented languages this cannot be handled in a nice way, because neither a.Collide(b) or b.Collide(a) is the correct approach; one would like to write (a,b).Collide() A specific example might be better here. Assume the following class hierarchy: Solid | +-- Asteroid | +-- Planet | + -- Earth | + -- Jupiter 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 (Solid,Solid) = " solids collided" collide (Planet, Asteroid) = collide (Asteroid, Planet) collide (Earth, Asteroid) = collide (Earth, Asteroid) So basically, the "best" collide function is picked, depending on the type of the arguments. How should I write Haskell code for something like this in general, in the sense that this hierarchy is typically huge and the matrix (of collide functions for each pair of types) is very sparse. Thanks, Peter No virus found in this outgoing message. Checked by AVG Free Edition. Version: 7.5.476 / Virus Database: 269.11.6/938 - Release Date: 05/08/2007 16:16

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.

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

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.

This is very nice, but it does not really solve the original problem. In your code, evaluating collide (Jupiter, Asteroid) will result in an endless loop. This is expected in your code, because no "inheritance" relation is present between e.g Jupiter and Planet. With multi-dispatch, it should pick the "best" matching collide function based on inheritance, or raise an error when ambiguous types. I could fix that be just keeping the "leafs" (Earth, Jupiter, Asteroid) as datatypes, and adding type classes for the "super classes" (Planet, Solid), like the code below, but I could not check Asteroid-Asteroid collision with that, GHCi gives an error. {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-} module Collide where class Collide a where collide :: a -> String data Asteroid = Asteroid data Jupiter = Jupiter data Earth = Earth class IsSolid a class IsSolid a => IsPlanet a instance IsSolid Asteroid instance IsSolid Jupiter instance IsSolid Earth instance IsPlanet Earth instance IsPlanet Jupiter instance (IsSolid a, IsSolid b) => Collide (a, b) where collide (x,y) = "generic collision" instance (IsPlanet a) => Collide (Asteroid, a) where collide (x,y) = "an asteroid hit a planet" instance (IsPlanet a) => Collide (a, Asteroid) where collide (x, y) = "an asteroid hit a planet" instance Collide (Asteroid, Earth) where collide (_,_) = "the end of the dinos" instance Collide (Earth, Asteroid) where collide (_,_) = "the end of the dinos" -- 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 ae = collide (Asteroid, Earth) ea = collide (Earth, Asteroid) ja = collide (Jupiter, Asteroid) aj = collide (Asteroid, Jupiter) -- However, this one gives an error? --aa = collide (Asteroid, Asteroid) -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Brian Hulley Sent: Monday, August 06, 2007 9:15 PM To: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Newbie question: "multi-methods" in Haskell 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. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

peterv wrote:
This is very nice, but it does not really solve the original problem.
To get Haskell to choose the best fit it's necessary to encode the location of each element in the hierarchy, so that elements deeper in the hierarchy are more instantiated than those at the top. Then instance selection chooses the best fit by just choosing the most instantiated match. Encoding can be done using phantom types, so a generic solid has the path IsSolid s a planet has IsSolid (IsPlanet p) and a specific planet eg Earth has path IsSolid (IsPlanet Earth) A newtype can be used to associate the path with the actual object: newtype InH path body = InH body so Earth is represented by InH Earth :: InH (IsSolid (IsPlanet Earth)) Earth A class with a functional dependency gives us the mapping between concrete objects and the objects as viewed by the hierarchy: class ToH body path | body -> path where toH :: body -> InH path body toH = InH The functional dependency means that the path (location in the hierarchy) is uniquely determined by the body, and instance decls then define this relationship: instance ToH Asteroid (IsSolid Asteroid) instance ToH Jupiter (IsSolid (IsPlanet Jupiter)) instance ToH Earth (IsSolid (IsPlanet Earth)) The code is below but as you can see the OOP encoding in Haskell becomes quite heavy and clunky so this style is probably not ideal for a real program - Tillmann's suggestion to use algebraic datatypes instead is more idiomatic - but anyway here goes: {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-} module Collide where class Collide a where collide :: a -> String data Asteroid = Asteroid data Jupiter = Jupiter data Earth = Earth data IsSolid a data IsPlanet a newtype InH path body = InH body class ToH body path | body -> path where toH :: body -> InH path body toH = InH instance ToH Asteroid (IsSolid Asteroid) instance ToH Jupiter (IsSolid (IsPlanet Jupiter)) instance ToH Earth (IsSolid (IsPlanet Earth)) data Collision = forall a. Collide a => Collision a mkCollision :: (ToH a pa, ToH b pb, Collide (InH pa a, InH pb b)) => a -> b -> Collision mkCollision a b = Collision (toH a, toH b) instance Collide (InH (IsSolid a) aa, InH (IsSolid b) bb) where collide _ = "generic collision" instance Collide (InH (IsSolid Asteroid) Asteroid, InH (IsSolid (IsPlanet bb)) cc) where collide _ = "an asteroid hit a planet" instance Collide (InH (IsSolid (IsPlanet a)) aa, InH (IsSolid Asteroid) Asteroid) where collide _ = "an asteroid hit a planet" instance Collide (InH (IsSolid Asteroid) Asteroid, InH (IsSolid (IsPlanet Earth)) Earth) where collide _ = "the end of the dinos" instance Collide (InH (IsSolid (IsPlanet Earth)) Earth, InH (IsSolid Asteroid) Asteroid) where collide _ = "the end of the dinos" instance Collide Collision where collide (Collision a) = collide a ----------------------- ghci output *Collide> mapM_ putStrLn (map collide [ mkCollision Asteroid Earth , mkCollision Earth Asteroid , mkCollision Jupiter Asteroid , mkCollision Asteroid Jupiter , mkCollision Asteroid Asteroid ]) the end of the dinos the end of the dinos an asteroid hit a planet an asteroid hit a planet generic collision *Collide> Best regards, Brian.

Remember that type classes do not provide object-oriented functionality. The dispatch is static, not dynamic.
I beg to disagree. map (\n. n + n) calls different (+) operations depending on the (type of the) argument list. That's why dictionaries are passed around (they are called vtables in many OO languages) by several Haskell implementations. Stefan

peterv schrieb:
In de book Modern C++ design, Andrei Alexandrescu writes that Haskell supports “multi-methods”
http://books.google.com/books?id=aJ1av7UFBPwC&pg=PA3&ots=YPiJ_nWi6Y&dq=moder n+C%2B%2B&sig=FWO6SVfIrgtCWifj9yYHj3bnplQ#PPA263,M1
Chapter 11, Page 263 of this books:
The C++ virtual function mechanism allows dispatching of a call depending on the dynamic type of one object. The multimethods feature allows dispatching of a function call depending on the types of multiple objects. A universally good implementation requires language support, wich is the route that languages such as CLOS, ML, Haskell, and Dylan have taken. C++ lacks such support, so it's emulation is left to library writers.
I do not see why the author of this book included Haskell in this list. (But from what I know, CLOS is more like a combinator library then like a language, so I don't understand the point of this list at all). Since Haskell has no language support for subtype polymorphism or dynamic dispatch of method calls, there are no dynamic multimethods either. But with multi-parameter typeclasses, we have statically dispatched multimethods, of course. (See Brian's answer). But the author speaks specifically about dynamic dispatch. Sometimes, class hierarchies from an OO design are naturally represented by algebraic data types. Then OO methods become ordinary haskell function, and dynamic dispatch becomes pattern matching, wich is of course possible on all argument positions: data Solid = Asteroid | Planet Planet data Planet = Earth | Jupiter collide :: Solid -> Solid -> String collide Asteroid (Planet Earth) = "the end of the dinos" collide Asteroid (Planet _) = "an asteroid hit a planet" collide p@(Planet _) Asteroid = collide Asteroid p collide _ _ = "solids collided" But you have to sort the definitons for collide yourself, because there is no "selection of the most specific" automatically. While this is a sometimes sensible translation of an OO design into an FP design, it is not the same thing as having objects and subtypes and dynamic dispatch. Tillmann
participants (5)
-
Brian Hulley
-
Dan Weston
-
peterv
-
Stefan Monnier
-
Tillmann Rendel