
Tom Poliquin escribió:
---------- 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
The problem here is you only can instance datatypes. The datatype here is FruitType. Banana is a DataConstructor. How to fix it? (I'm newbie too, so you have to think more with my answer) A posibility is create a data type for each frute: ----- [...] class FruitType a where volume :: Fruit a -> Double -- default spherical volume F{radius=r,len=l} = (4.0/3.0) * pi * r * r * r data Orange = Orange data Apple = Apple data Banana = Banana data Watermelon = Watermelon instance FruitType Orange where instance FruitType Apple where instance FruitType Banana where volume F{radius=r,len=l} = pi * (r * r) * l instance FruitType Watermelon where volume F{radius=r,len=l} = (4.0/3.0) * pi * (2.0 * r) * l * (0.5 * l) [...] ----- But, you can't later define a list with mixed types because the first one is "::Fruit Orange" and the second is "::Fruit Apple" ----- WRONG vvv initFruit :: FruitType a => [Fruit a] 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) ] ----- WRONG ^^^ The second posibilitie is use patterns. So, I'm sorry this example is very similar to your first attempt: ----- SECOND ATTEMPT module Main where data Fruit a = F {radius::Double, len::Double, fType::a} data FruitType = Orange | Apple | Banana | Watermelon deriving Show class Volume a where volume:: a -> Double instance Volume (Fruit FruitType) where 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) volume F{radius=r,len=l} = (4.0/3.0) * pi * r * r * r 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 But, you need define "FlexibleInstances" add on because: "instance Volume (Fruit FruitType)" is not standard Haskell THIRD IDEA. Make a wrapper volume function: ----- module Main where data Fruit a = F {radius::Double, len::Double, fType::a} data FruitType = Orange | Apple | Banana | Watermelon deriving Show class Volume a where volume:: a -> Double -> Double -> Double instance Volume FruitType where volume Banana r l = pi * (r * r) * l volume Watermelon r l = (4.0/3.0) * pi * (2.0 * r) * l * (0.5 * l) volume _ r l = (4.0/3.0) * pi * r * r * r volumeFruit F{radius=r,len=l,fType=f} = volume f r 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 let fruit = initFruit mapM (\f@(F{fType=t}) -> putStrLn ("Volume -> " ++ show t ++ " = " ++ show (volumeFruit f))) fruit ----- So. This problem is more interesting that I thought. Javier M Mora. PD. initFruit is a Pure Function. I prefer the "let" construction.