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

Brian Hulley brianh at metamilk.com
Tue Aug 7 00:49:57 EDT 2007


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.


More information about the Haskell-Cafe mailing list