
I've been writing Haskell programs (even useful ones :-) ) for awhile and I thought it was time to experiment with my own type classes. I chose the (contrived toy) problem of computing the volume of various fruits. First I wrote the code using algebraic data types .. (shown below); then I 'converted' it to use type classes (also shown below) The type class version gives me the errors .. Main.hs:12:16: Not in scope: type constructor or class `Banana' Main.hs:15:16: Not in scope: type constructor or class `Watermelon' .. which makes sense since Banana and Watermelon are 'data constructors' and not 'type constructors'. The problem is I'm not sure how to get around it .. If I try putting data Orange = Orange data Banana = Banana .. then what does 'initFruit' return .. ? it can't return [Fruit FruitType] anymore .. It seems like this should be a simple problem. I'm clearly not 'getting it'. Any help greatly appreciated, Tom ---------- Algegraic Data Type Version (works) ---------- module Main where data Fruit a = F {radius::Double, len::Double, fType::a} data FruitType = Orange | Apple | Banana | Watermelon deriving Show initFruit :: [Fruit FruitType] initFruit = [ (F 3.0 0.0 Orange), (F 3.0 0.0 Apple), (F 3.0 2.0 Banana), (F 40.0 20.0 Watermelon) ] volume :: Fruit FruitType -> Double volume F{radius=r,len=l,fType=Orange} = (4.0/3.0) * pi * r * r * r volume F{radius=r,len=l,fType=Apple} = (4.0/3.0) * pi * r * r * r volume F{radius=r,len=l,fType=Banana} = pi * (r * r) * l volume F{radius=r,len=l,fType=Watermelon} = (4.0/3.0) * pi * (2.0 * r) * l * (0.5 * l) ---------- -- Main -- ---------- main = do fruit <- return $ initFruit mapM (\f@(F{fType=t}) -> putStrLn ("Volume -> " ++ show t ++ " = " ++ show (volume f))) fruit Volume -> Orange = 113.09733552923255 Volume -> Apple = 113.09733552923255 Volume -> Banana = 56.548667764616276 Volume -> Watermelon = 67020.64327658225 ---------- Type Class Version (fails) ---------- module Main where data Fruit a = F {radius::Double, len::Double, fType::a} data FruitType = Orange | Apple | Banana | Watermelon class Volume a where volume :: (FruitType a) => Fruit a -> Double -- default spherical fruit .. volume F{radius=r,len=l} = (4.0/3.0) * pi * r * r * r instance Volume Banana where volume F{radius=r,len=l} = pi * (r * r) * l instance Volume Watermelon where volume F{radius=r,len=l} = (4.0/3.0) * pi * (2.0 * r) * l * (0.5 * l) initFruit :: [Fruit FruitType] initFruit = [ (F 3.0 0.0 Orange), (F 3.0 0.0 Apple), (F 3.0 2.0 Banana), (F 40.0 20.0 Watermelon) ] ---------- -- Main -- ---------- main = do fruit <- return $ initFruit mapM (\f@(F{fType=t}) -> putStrLn ("Volume -> " ++ show t ++ " = " ++ show (volume f))) fruit Main.hs:12:16: Not in scope: type constructor or class `Banana' Main.hs:15:16: Not in scope: type constructor or class `Watermelon'