[Haskell-beginners] Re: Type Class Woes ..
Tom Poliquin
poliquin at softcomp.com
Mon Aug 31 15:02:36 EDT 2009
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<poliquin at softcomp.com> 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.
> ;)
More information about the Beginners
mailing list