It's hard to say what really is 2d or 3d. Think about closed 3d curve (points placed in 3d space somehow). Is it 2d or 3d? Depends on the interpretation.
Usually DCC packages don't care about this. And I wouldn't too :p Who needs extra level of complexity without any reason?

On Tue, Sep 15, 2009 at 3:48 PM, Tom Nielsen <tanielsen@gmail.com> wrote:
I think you are in trouble because you have mixed 2D and 3D shapes in
one data type.

--not checked for typos, syntax, idiocy etc.
{-# LANGUAGE GADTs #-}

data Z
data S n

type Two = S (S Z)
type Three = S Two

data Geometry dims where
   Sphere :: Position -> Radius -> Geometry Three
   Cylinder :: Position -> Radius -> Height -> Geometry Three
   Circle :: Position -> Radius -> Geometry Two

   Postcard :: Position -> Orientation -> Geometry Two -> Geometry Three

perimeter :: Geometry Two -> Double
perimeter (Circle _ r) = 2*pi*r

Tom

On Tue, Sep 15, 2009 at 11:29 AM, 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
>
>