[Haskell-beginners] Program reliability and multiple data constructors; polymorphism

Tim Perry tim.v2.0 at gmail.com
Thu Apr 19 18:04:23 CEST 2012


On Wed, Apr 18, 2012 at 8:10 AM, umptious <umptious at gmail.com> wrote:

> One of the programming exercises I keep evolving as I learn Haskell is a
> toy 2D shape editor with four primitives:
>
> data Shape =   Circle   {origin::Pt2, radius::Float}
>                        | Square   {origin::Pt2, side  ::Float}
>                        | Rect     {origin::Pt2, other ::Pt2}
>                        | Composite {shapes::[Shape]}
>                          deriving (Show, Read)
>
> The intent  is Composites can contain Shapes of any kind, including other
> Composites so that you can apply transformations to a Composite and these
> will be applied to the contained Shapes recursively. So an arm might
> contain a hand which constains a dozen or so Rects. Transform the arm and
> the hand and rects should transform; transform the hand and its rects
> should transform but the not arm. Big deal.
>
> And the above makes that really easy when you know you're talking to a
> Composite. But now I've hit an intellectual stumbling point and the books
> and source I have don't seem to address it:  I can apply the destructuring
> command "shapes" defined in the cstr "Composite" to ANY Shape. And if I do
> that to say a circle, BLAM! Or if I apply "radius" to Rect, BLAM! At
> runtime. No type checking support (because yes, they're the same type.)
>

Well, if you have a Shape, you do not know what data type you have and
neither does the compiler. However, you can code a function, say shapeList,
which always gives you a list of Shapes regardless of what type of Shape
gets past in:

shapeList :: Shape -> [Shape]
shapeList (Composite shapes) = shapes
shapeList s = [s]

Lesson: don't use record syntax on a heterogeneous collection. I'm
surprised the compiler doesn't complain when record syntax
isn't guaranteed to succeed.

As a general comment, it looks like you are trying to code C++ or Java
style OO code in Haskell. I can say from experience, it doesn't work well.

Generally, envision your functions to work on a class of abstract data
types (ATDs). Generalize this class of ATDs into a typeclass. Write an
instance of the function to operate on each ADT you want to be a member of
a typeclass. So, if I was going to write some code to handle shapes I might
do it like the following. Be warned, I'm far from a Haskell Guru, but I
think this is a better approach. Hopefully we'll get an improved bit of
code....

import Data.List

data Pt2 = Pt2 { x :: Float , y :: Float } deriving (Show, Read)

data Circle =  Circle { originCircle :: Pt2 , radius :: Float } deriving
(Show, Read)

data Square =    Square   { originSquare ::Pt2 , side  :: Float } deriving
(Show, Read)

data Rect =      Rect {originRect ::Pt2, other :: Pt2} deriving (Show, Read)

data Composite = Composite { circles :: [Circle]
                           , squares :: [Square]
                           , rects   :: [Rect]
                           }

class Shape a where
   area :: a -> Float
   minx :: a -> Float
   miny :: a -> Float

instance Shape Circle where
   area (Circle _ r) = r * r * pi
   minx (Circle (Pt2 x _) r) = x - r
   miny (Circle (Pt2 _ y) r) = y - r

instance Shape Square where
   area (Square _ side) = side*side
   minx (Square (Pt2 x y) side) = if side < 0
                                     then x + side
                                     else x
   miny (Square (Pt2 x y) side) = if side < 0
                                     then y + side
                                     else y

instance Shape Rect where
   area (Rect (Pt2 x1 y1) (Pt2 x2 y2)) = abs((x2 - x1) * (y2 - y1))
   minx (Rect (Pt2 x1 y1) (Pt2 x2 y2)) = min x1 x2
   miny (Rect (Pt2 x1 y1) (Pt2 x2 y2)) = min y1 y2

instance Shape Composite where
   area (Composite cs ss rs) = (sum $ map area cs) + (sum $ map area ss) +
(sum $ map area rs)
   minx (Composite cs ss rs) = Data.List.minimum(map minx cs ++ map minx ss
++ map minx rs)
   miny (Composite cs ss rs) = Data.List.minimum(map miny cs ++ map miny ss
++ map miny rs)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20120419/fbcdf509/attachment.htm>


More information about the Beginners mailing list