
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'

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.

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

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

On Sun, Aug 30, 2009 at 9:14 PM, Tom Poliquin
Chaddaï Fouché wrote:
data Volumic = Volume a => V a
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.
Oops... Sorry, I just put together a simple example and didn't test it, I forgot the forall :
data Volumic = forall a . (Volume a) => V a
You must explicitly quantify the type variable to do existentials (and use the proper extensions, which you did).
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.
Well it is a _toy_ problem where you're specifically trying to shoehorn something into the form you wished to discover, this kind of thing sometimes seems harder to do than resolve real problems where the context and the practical objectives give you clues all along.
- The problem is *not* a toy problem and is really complicated.
In fact you're trying to address the so called "Expression problem" here, it isn't a simple feat and while Haskell bring some answer they are not so straightforwardly supported and easy to use as could be wished (though I'm unaware of any practical language that do better currently IMHO).
- Type classes are more appropriate at the 'system' level than the 'application' level. Applications are better off using algebraic data types.
Depend on what you call "Application" I guess, given that creating a big application in Haskell seems to consist of creating a framework/dsl to express the main program in two lines, it may be that you'll still need type class for that, but it's true that type classes are better placed in libraries than in the application code, where algebraic/record type and pattern matching are often a more appropriate solution.
- 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!!!
It may be that too, while Haskell is impressive, it isn't perfect just yet. ;) -- Jedaï

Tom Poliquin wrote:
I chose the (contrived toy) problem of computing the volume of various fruits.
Chaddaï Fouché wrote:
....you can still have a list of different fruits type, using existential types,
[ Code supplied]
Chaddai .. I added the 'forall' and it works great! Thanks very much for the code and the 'philosophical' comments ! Full code of your solution below. Tom {-# OPTIONS_GHC -XFlexibleInstances #-} {-# OPTIONS_GHC -XExistentialQuantification #-} {-# OPTIONS_GHC -XEmptyDataDecls #-} module Main where data Fruit a = F {radius, length :: Double } data Orange; data Banana -- empty data decls 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 -- flexible instances vol (F r l) = pi * (r * r) * l data Volumic = forall a . (Volume a) => V a -- existential quantification fruit_list :: [Volumic] fruit_list = [ V (F 3 undefined :: Fruit Orange) ,V (F 1 6 :: Fruit Banana) ] main = do fruit <- return $ fruit_list mapM (\(V f) -> putStrLn ("Volume -> " ++ " = " ++ show (vol f))) fruit ------------------------------------------------------
On Sun, Aug 30, 2009 at 9:14 PM, Tom Poliquin
wrote: Chaddaï Fouché wrote:
data Volumic = Volume a => V a
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.
Oops... Sorry, I just put together a simple example and didn't test
it, I forgot the forall :
data Volumic = forall a . (Volume a) => V a
You must explicitly quantify the type variable to do existentials (and use the proper extensions, which you did).
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.
Well it is a _toy_ problem where you're specifically trying to shoehorn something into the form you wished to discover, this kind of thing sometimes seems harder to do than resolve real problems where the context and the practical objectives give you clues all along.
- The problem is *not* a toy problem and is really complicated.
In fact you're trying to address the so called "Expression problem" here, it isn't a simple feat and while Haskell bring some answer they are not so straightforwardly supported and easy to use as could be wished (though I'm unaware of any practical language that do better currently IMHO).
- Type classes are more appropriate at the 'system' level than the 'application' level. Applications are better off using algebraic data types.
Depend on what you call "Application" I guess, given that creating a big application in Haskell seems to consist of creating a framework/dsl to express the main program in two lines, it may be that you'll still need type class for that, but it's true that type classes are better placed in libraries than in the application code, where algebraic/record type and pattern matching are often a more appropriate solution.
- 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!!!
It may be that too, while Haskell is impressive, it isn't perfect just yet. ;)

Hi, 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)
Can anyone explain the above pattern matching syntax? I've never seen it before... Thanks, Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Am Sonntag 30 August 2009 14:32:56 schrieb Patrick LeBoutillier:
Hi,
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)
Can anyone explain the above pattern matching syntax? I've never seen it before...
Thanks,
Patrick
It's named-field syntax, cf. http://haskell.org/onlinereport/exps.html#sect3.15 If you have a type with named fields, like data FType = Con1 { field1 :: Int, field2 :: Bool } | Con2 { field1 :: Int, field3 :: Char } you can pattern-match either by position: fun (Con1 i b) = ... or by named field syntax: fun Con1{field2=True, field1=x} = ... -- corresponds to fun (Con1 x True) fun Con2{field3='a'} = ... -- fun (Con2 _ 'a') It's very convenient if you need only a few arguments of a multi-argument constructor: fun C{fieldx=y} vs. fun (C _ _ _ _ _ y _ _ _ _)

On Sun, Aug 30, 2009 at 2:32 PM, Patrick
LeBoutillier
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)
Can anyone explain the above pattern matching syntax? I've never seen it before...
It's part of what record syntax allows : record pattern. record_pattern = data_constructor '{' (field_pattern ',')* '}' field_pattern = field_name '=' pattern You don't have to use all the fields of the datatype in a pattern if you don't need them all. A special case is when you put zero field_pattern in the {}, in this case you can even use this syntax for regular datatype (no record syntax), to write thing like :
isJust Just {} = True isJust _ = False
(especially interesting for constructors with plenty of parameters, of course) ----------- 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. -- Jedaï
participants (6)
-
Chaddaï Fouché
-
Daniel Fischer
-
Javier M Mora
-
Patrick LeBoutillier
-
Tim Attwood
-
Tom Poliquin