Well... How this:

instance Encircled Geometry where
       perimeter (Sphere _ r) = Nothing
       perimeter (Circle _ r) = Just $ 2.0 * pi * r

differs from this:

perimeter :: Geometry -> Maybe Double
perimeter (Sphere _ r) = Nothing
perimeter (Circle _ r) = Just $ 2.0 * pi * r

and from this:

perimeter :: Geometry -> Double
perimeter (Sphere _ r) = 0.0
perimeter (Circle _ r) = 2.0 * pi * r

The latter is even simpler because there is no need in extraction of Double value from Maybe.
So the question is still there: do I need a type class?

On Tue, Sep 15, 2009 at 12:21 PM, Olex P <hoknamahn@gmail.com> wrote:
Sure! I completely forgot about Maybe. The only one question is is it good from the point of view of ordinary user who doesn't know about such things like functional programming, monads etc. Imagine average user who is looking into a spreadsheet and sees values 0.1, 1.4, Nothing... From other side it seems to be logical. Why not.
Thanks for the idea :)

On Tue, Sep 15, 2009 at 12:05 PM, Lyndon Maydwell <maydwell@gmail.com> wrote:
I think the problem is that you want to compose a list with no
indication of weather one member can have a perimeter or not. I'm not
sure if this is a good solution or not, but I immediately think to
make all Geometry objects instances of a class that return a Maybe
value for the perimeter:

e.g.

---

import Data.Maybe

data Geometry = Sphere Position Radius | Circle Position Radius deriving (Show)

type Position = (Double, Double)
type Radius = Double
type Height = Double

class Encircled x where
       perimeter :: x -> Maybe Double

instance Encircled Geometry where
       perimeter (Sphere _ r) = Nothing
       perimeter (Circle _ r) = Just $ 2.0 * pi * r

list = [Sphere (1,1) 1, Circle (2,2) 2]

main = (print . catMaybes . map perimeter) list

--- [12.566370614359172]

On Tue, Sep 15, 2009 at 6:29 PM, Olex P <hoknamahn@gmail.com> wrote:
> Hey guys,
>
> It's a dumb question but I'd like to know a right answer...
> Let's say we have some geometry data that can be Sphere, Cylinder, Circle
> and so on. We can implement it as new data type plus a bunch of functions
> that work on this data:
>
> data Geometry = Sphere Position Radius
>                         | Cylinder Position Radius Height
>                         | Circle Position Radius
>                         deriving (Show)
>
> perimeter (Sphere _ r) = 0.0
> perimeter (Cylinder _ r h) = 0.0
> perimeter (Circle _ r) = 2.0 * pi * r
>
> Perimeter doesn't make sense for Sphere or Cylinder. So we could define a
> type class for objects that have perimeter and make an instance of it only
> for Circle (data Circle = Circle Position Radius). Make sense. But these
> three functions above have desired behaviour. If user has a list of objects
> like [Sphere, Circle, Circle, Cylinder] he would like to calculate
> perimeters of each object using map perimerer list (in this case we also
> have to modify Geometry data type).
> So we could make instances of "perimeter" type class for all objects and
> return zero in case if perimeter doesn't make sense.
> Same as previous version but with typeclasses and with additional
> constructors (constructors for each type of object + constructors in
> Geometry data). Looks a bit overcomplicated.
> Any reasons to use type classes in this case? Maybe there is something I'm
> missing?
>
> Cheers,
> -O
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>