[Haskell-beginners] Re: Type Class Woes ..

Tim Attwood timothyea at comcast.net
Sun Aug 30 06:57:47 EDT 2009


Orange, Apple etc are values of type FruitType, not types themselves.

module Main where

data FruitType = Orange | Apple | Banana | Watermelon deriving (Eq, Show)
data Fruit = Fruit {fruitRadius::Double, fruitLength::Double, 
fType::FruitType}

data VegType = Tomato | StringBean deriving (Eq, Show)
data Veg = Veg {vegRadius::Double, vegLength::Double, vType::VegType}

data GeoType = Sphere | Elipsoid deriving (Eq, Show)
data Geometric = Geo {radius1::Double, radius2::Double, radius3::Double, 
gType::GeoType}

class ObjectCalc a where
   volume :: a -> Double
   surfaceArea :: a -> Double

instance ObjectCalc Geometric where
   volume g | gType g == Sphere   = (4.0/3.0) * pi * ( (radius1 g) ** 3.0)
            | gType g == Elipsoid = (4.0/3.0) * pi * (radius1 g) * (radius2 
g) * (radius3 g)
            | otherwise = undefined
   surfaceArea g = undefined

instance ObjectCalc Fruit where
   volume f | fType f == Orange     = volume (Geo (fruitRadius f) undefined 
undefined Sphere)
            | fType f == Apple      = volume (Geo (fruitRadius f) undefined 
undefined Sphere)
            | fType f == Banana     = volume (Geo (fruitRadius f) 
(fruitRadius f) (fruitLength f) Elipsoid)
            | fType f == Watermelon = volume (Geo ((fruitRadius f)*2.0) 
((fruitLength f)*0.5) (fruitLength f) Elipsoid)
            | otherwise             = undefined
   surfaceArea f = undefined

instance ObjectCalc Veg where
   volume v = undefined
   surfaceArea v = undefined

initFruit :: [Fruit]
initFruit = [
              (Fruit  3.0  0.0 Orange),
              (Fruit  3.0  0.0 Apple),
              (Fruit  3.0  2.0 Banana),
              (Fruit 40.0 20.0 Watermelon)
            ]

main =
   let f = initFruit
       v = map volume f
       ft = map fType f
       s = zipWith (\a b -> putStrLn ("Volume -> " ++ (show a) ++ " = " ++ 
(show b))) ft v
   in sequence_ s 




More information about the Beginners mailing list