[Haskell-cafe] Translation of Haskell type classes
Enrique Martín
emartinm at fdi.ucm.es
Thu Feb 4 10:32:24 EST 2010
Hello all,
few days ago I made some experiments with Haskell type classes. I wrote
a small Haskell program for searching in sorted lists, defining my own
type classes for equality (MyEq) and order (MyOrd) so that they only
have one member function:
--------------------------------------------------------
class MyEq a where
eq :: a -> a -> Bool
class MyEq a => MyOrd a where
less :: a -> a -> Bool
data Nat = Z | S Nat
instance MyEq Nat where
eq Z Z = True
eq Z (S x) = False
eq (S x) Z = False
eq (S x) (S y) = eq x y
instance MyOrd Nat where
less Z Z = False
less Z (S x) = True
less (S x ) Z = False
less (S x) (S y) = less x y
search :: MyOrd a => a -> [a] -> Bool
search x [] = False
search x (y:ys) = (eq x y) || (less y x && search x ys)
--------------------------------------------------------
I also wrote the translation of this program using the classical
approach of dictionaries that appears in "How to make ad-hoc
polymorphism less ad hoc", Wadler & Blott 1989 or "Type Classes in
Haskell", Cordelia V. Hall et. al. 1996.
--------------------------------------------------------
-- From the definition of type class MyEq
data DictMyEq a = DictMyEq (a -> a -> Bool)
eq :: DictMyEq a -> (a -> a -> Bool)
eq (DictMyEq x) = x
-- From the definition of type class MyOrd
data DictMyOrd a = DictMyOrd (DictMyEq a) (a -> a -> Bool)
getMyEqFromMyOrd :: DictMyOrd a -> DictMyEq a
getMyEqFromMyOrd (DictMyOrd x y) = x
less :: DictMyOrd a -> (a -> a -> Bool)
less (DictMyOrd x y) = y
data Nat = Z | S Nat
-- From the instance MyEq Nat
eqNat :: Nat -> Nat -> Bool
eqNat Z Z = True
eqNat Z (S x) = False
eqNat (S x) Z = False
eqNat (S x) (S y) = eqNat x y
dictMyEqNat :: DictMyEq Nat
dictMyEqNat = DictMyEq eqNat
-- From the instance MyOrd Nat
lessNat :: Nat -> Nat -> Bool
lessNat Z Z = False
lessNat Z (S x) = True
lessNat (S x ) Z = False
lessNat (S x) (S y) = lessNat x y
dictMyOrdNat :: DictMyOrd Nat
dictMyOrdNat = DictMyOrd dictMyEqNat lessNat
search :: DictMyOrd a -> a -> [a] -> Bool
search _ x [] = False
search dict x (y:ys) = (eq (getMyEqFromMyOrd dict) x y) || (less dict y
x && search dict x ys)
--------------------------------------------------------
I made some tests in GHC 6.8.2 and I noticed that the original program
with type classes runs pretty faster than the translated program. For
example, reducing the expression
search (S Z) (replicate 1000000 Z)
needs 2.07 seconds in the original program. However the translated
expression
search dictMyOrdNat (S Z) (replicate 1000000 Z)
needs 3.10 seconds in the translated program, which is one more second.
Surprised with the results, I repeated the test this time in Hugs Sept.
2006. I noticed that the difference was not so big:
search (S Z) (replicate 100000 Z) --> (2100051 reductions,
2798068 cells, 2 garbage collections)
search dictMyOrdNat (S Z) (replicate 100000 Z) --> (2200051
reductions, 2898067 cells, 3 garbage collections)
My first idea was that type classes were implemented using the approach
of dictionaries, but the test showed me that it is not true (mainly in
GHC). Then I discovered the paper "Implementing Haskell overloading",
Augustsson 1993, when he describes some ways to improve the speed of
Haskell overloading.
So my questions are:
1) is the enhancement obtained only using the optimizations of
Augustsson's paper?
2) Could anyone tell me where I can find the translation of type
classes that GHC and Hugs use?
Thank you very much,
Enrique M.
More information about the Haskell-Cafe
mailing list