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

Tom Poliquin poliquin at softcomp.com
Sun Aug 30 15:14:57 EDT 2009


Thanks everyone for the replies!
Comments below ..

Tom Poliquin wrote:

> I chose the (contrived toy) problem of computing the volume
> of various fruits.

> First I wrote the code using algebraic data types ..
> ...then I 'converted' it to use type classes
> 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'


On Sunday 30 August 2009 03:57, Tim Attwood wrote:

> 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

This looks great .. it even added an extra idea ....
that different fruit/vegs have different geometric shapes .. Abstractly
then ..

'Grown Things' each have a geometric shape, then each geometric
shape has a method for computing volume and surface area ..


Javier M Mora wrote:

> 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.

This has the flavor (no pun intended) of pattern matching
since there's only one instance ..


Chaddaï Fouché  wrote:

> To come back to the initial subject, if you use datatypes and
> typeclass rather than dataconstructors and pattern matching to allow
> extensibility of data, you can still have a list of different fruits
> type, using existential types, though that is not without minus :

> data Fruit a = F { radius, length :: Double }
> data Orange; data Banana;
>
> class Volume a where
>   vol :: a -> Double
>
> instance Volume (Fruit Orange) where
>   vol (F r _) = (4/3) * pi * r * r * r
> instance Volume (Fruit Banana) where
>   vol (F r l) = pi * (r * r) * l
>
> data Volumic = Volume a => V a
>
> fruit_list :: [Volumic]
> fruit_list = [V (F 3 undefined :: Fruit Orange), V (F 1 6 :: Fruit Banana) ]

> In this particular case it is really uninteresting since you could as
> well stock a list of volumes (the only thing you can do with a Volumic
> is get the volume of its content) but with more versatile typeclass,
> it may be different.

I've never used existentials .. but this seems like a powerful idea. 
Unfortunately I couldn't get this to compile ..
It was unhappy about 'data Volumic' so I changed it to
'data Volumic a' .. it was still unhappy and took me down
the road of compiler switch options .. until I had ..
ghc -XFlexibleInstances -XExistentialQuantification -XEmptyDataDecls --make 
Main.hs
which was also unsuccessful.


Philosophical Summary ...
All the examples of type classes examples I've seen in tutorials and
books look simple, beautiful and elegant. No disrespect intended
to the coding suggestions but they seem a little more difficult than
I had expected for my toy problem ..

So I'm wondering why that is ..

- I'm stupidly trying to shoehorn my toy problem
  into a type class example which is not the best approach.

- The problem is *not* a toy problem and is really
   complicated.

- Type classes are more appropriate at the 'system' level
   than the 'application' level. Applications are better off
   using algebraic data types.

- Tom (me) has expectations that are too high.
   I do have high expectations of Haskell. I've written
   several mid sized applications (obviously without
   using type classes :-) ) and found them easy to write
   and unbelievably easy to refactor!!!

Thoughts appreciated.

Thanks again to eveyone!

Tom
   






More information about the Beginners mailing list