Program reliability and multiple data constructors; polymorphism

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.) To me this seems alarming. It means that I can't reason about the safety of my program based on type checking as I'd like. And none of the answers I can think seem at all elegant: - I could use exception handling, but that means carefully checking which data declarations are potential bombs and using exceptions only when they are involved - hideously error prone - or using exceptions everywhere. Which is just hideous. - I could hack run time type checking using the ctsr info in "show". But again I'd have to know when to use it or use it everywhere. And it seems like a ridiculous kludge to bring to a language that has been designed for elegance. ..So what is the Haskell idiom for dealing with this??? In fact I suppose I'm asking two questions: 1. How do I re-design this program so it is safe (use class and instance maybe, abandoning use of a single data type? but I then have to have separate Lists for each type, even if they derived from a common class?) 2. How can one use compile time checking or (less good) coding practices to eliminate the possibilty of such runtime exceptions? And come to think of it 3. is there a Haskell book which addresses design and structural problems like this one - which I would have thought was both obvious and fundamental - because of the books I've looked at so far seem to do a tolerable job. The best of them present an adequate "on rails" tour, but none of them seem to give you the tools to address issues like this one. Whereas with C++and Stroustrupp, Common Lisp and Graham, the Smalltalk book, and I Erlang and Armstrong I'd know exactly what to do. Admittedly the C++ solutions wouldn't be pretty, but anything the compiled would be safe to run (unless I went to great efforts otherwise..)

There is some funkyness going on with records there.
You can sidestep the issue by giving each constructor its own type of
argument record:
type Pt2 = (Float, Float)
data Shape = Circle CircleData
| Square SquareData
| Rect RectData
| Composite CompData
deriving (Show, Read)
data CircleData = CircD {circleOrigin :: Pt2, radius :: Float}
deriving (Show, Read)
data SquareData = SquareD {squareOrigin :: Pt2, side :: Float}
deriving (Show, Read)
data RectData = RectD {bottomLeft :: Pt2, topRight :: Pt2}
deriving (Show, Read)
newtype CompData = CompD {shapes :: [Shape] }
deriving (Show, Read)
x = shapes $ RectD (0,0) (1,1) -- Throws an error on compile
I'm not sure what is going on in your example, but it seems like each
constructor adds its record argument's fields to a shared record type
or some such magic. Nasty.
On Wed, Apr 18, 2012 at 11:10 PM, umptious
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.)
To me this seems alarming. It means that I can't reason about the safety of my program based on type checking as I'd like. And none of the answers I can think seem at all elegant:
- I could use exception handling, but that means carefully checking which data declarations are potential bombs and using exceptions only when they are involved - hideously error prone - or using exceptions everywhere. Which is just hideous.
- I could hack run time type checking using the ctsr info in "show". But again I'd have to know when to use it or use it everywhere. And it seems like a ridiculous kludge to bring to a language that has been designed for elegance.
..So what is the Haskell idiom for dealing with this??? In fact I suppose I'm asking two questions:
1. How do I re-design this program so it is safe (use class and instance maybe, abandoning use of a single data type? but I then have to have separate Lists for each type, even if they derived from a common class?)
2. How can one use compile time checking or (less good) coding practices to eliminate the possibilty of such runtime exceptions?
And come to think of it
3. is there a Haskell book which addresses design and structural problems like this one - which I would have thought was both obvious and fundamental - because of the books I've looked at so far seem to do a tolerable job. The best of them present an adequate "on rails" tour, but none of them seem to give you the tools to address issues like this one. Whereas with C++and Stroustrupp, Common Lisp and Graham, the Smalltalk book, and I Erlang and Armstrong I'd know exactly what to do. Admittedly the C++ solutions wouldn't be pretty, but anything the compiled would be safe to run (unless I went to great efforts otherwise..)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Re. my previous post below, I'm guessing that the most elegant solution to
the problem of how to get the program to work is to hide all the cstrs and
only let access be through functions using record syntax like this Haskell
wiki example:
data Foo2 = Bar2 | Baz2 {barNumber::Int, barName::String}
--Using records allows doing matching and binding only for the variables
relevant to the function we're writing, making code much clearer:
h :: Foo2 -> Int
h Baz2 {barName=name} = length name
h Bar2 {} = 0
--Also, the {} pattern can be used for matching a constructor regardless of
the datatype elements even if you don't use records in the data declaration:
data Foo = Bar | Baz Int
g :: Foo -> Bool
g Bar {} = True
g Baz {} = False
main = do
print $ h a
print $ h b
where
a = Bar2
b = Baz2{barNumber=1, barName="fredikins"}
...Is this correct? And if so, is the answer to my second question "There's
no way of getting the compiler to guarantee runtime safety, so when you
have record syntax ctsrs for the same type which create objects with
different data, hide the ctsrs"?
On 18 April 2012 16:10, umptious
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.)
To me this seems alarming. It means that I can't reason about the safety of my program based on type checking as I'd like. And none of the answers I can think seem at all elegant:
- I could use exception handling, but that means carefully checking which data declarations are potential bombs and using exceptions only when they are involved - hideously error prone - or using exceptions everywhere. Which is just hideous.
- I could hack run time type checking using the ctsr info in "show". But again I'd have to know when to use it or use it everywhere. And it seems like a ridiculous kludge to bring to a language that has been designed for elegance.
..So what is the Haskell idiom for dealing with this??? In fact I suppose I'm asking two questions:
1. How do I re-design this program so it is safe (use class and instance maybe, abandoning use of a single data type? but I then have to have separate Lists for each type, even if they derived from a common class?)
2. How can one use compile time checking or (less good) coding practices to eliminate the possibilty of such runtime exceptions?
And come to think of it
3. is there a Haskell book which addresses design and structural problems like this one - which I would have thought was both obvious and fundamental - because of the books I've looked at so far seem to do a tolerable job. The best of them present an adequate "on rails" tour, but none of them seem to give you the tools to address issues like this one. Whereas with C++and Stroustrupp, Common Lisp and Graham, the Smalltalk book, and I Erlang and Armstrong I'd know exactly what to do. Admittedly the C++ solutions wouldn't be pretty, but anything the compiled would be safe to run (unless I went to great efforts otherwise..)

And in partially answering my own question I forgot to add that this gives you a less queasy-making way of identifying the cstr used to create a structure: --Also, the {} pattern can be used for matching a constructor regardless of
the datatype elements even if you don't use records in the data declaration:
data Foo = Bar | Baz Int g :: Foo -> Bool g Bar {} = True g Baz {} = False
Regarding my comments on the lack of good Haskell books, I just checked LYAHFAGG and RWH and neither of them covered either the problem, or the two mechanisms used for a solution. This is very poor, given that the problem is such an obvious one and the solutions are such general mechanisms. I'm pretty sure that Hutton doesn't cover this either - in fact "record syntax" isn't even in the index.

If you want type safety, then use different types (data Circle, data
Rectangle, ..) and implement the properties you want via classes, i.e
'class HasRadius a', 'class HasSomethingElse a' and some such. Right
now you only have one type, and wanting it to be type safe at that is,
khm ..impossible.
In general, for all of what you program you should have some specific
goal in mind, a concrete outcome. For the radius problem the solution
could also be (instead of having it as a class) of giving it the type
of 'Shape -> Maybe Float' and have it return 'Nothing' when radius
isn't applicable. When you just tinker away and try to solve all of 2D
geometry with it, or any part of it at random, usually leads to
nowhere (for me at least).
Edit:
Just noticed the subject which says "polymorphism" at the end.
In Haskell you can have structural polymorphism, like 'data X a = X a'
where 'X a' is polymorphic at 'a' -- you can have any type at the
place of 'a'. Or or ad hoc polymorphism -- the thing that classes do.
The Shape data type in the initial post is monomorphic and recursive.
On Wed, Apr 18, 2012 at 7:14 PM, umptious
Re. my previous post below, I'm guessing that the most elegant solution to the problem of how to get the program to work is to hide all the cstrs and only let access be through functions using record syntax like this Haskell wiki example:
data Foo2 = Bar2 | Baz2 {barNumber::Int, barName::String}
--Using records allows doing matching and binding only for the variables relevant to the function we're writing, making code much clearer:
h :: Foo2 -> Int h Baz2 {barName=name} = length name h Bar2 {} = 0
--Also, the {} pattern can be used for matching a constructor regardless of the datatype elements even if you don't use records in the data declaration:
data Foo = Bar | Baz Int g :: Foo -> Bool g Bar {} = True g Baz {} = False
main = do print $ h a print $ h b where a = Bar2 b = Baz2{barNumber=1, barName="fredikins"}
...Is this correct? And if so, is the answer to my second question "There's no way of getting the compiler to guarantee runtime safety, so when you have record syntax ctsrs for the same type which create objects with different data, hide the ctsrs"?
On 18 April 2012 16:10, umptious
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.)
To me this seems alarming. It means that I can't reason about the safety of my program based on type checking as I'd like. And none of the answers I can think seem at all elegant:
- I could use exception handling, but that means carefully checking which data declarations are potential bombs and using exceptions only when they are involved - hideously error prone - or using exceptions everywhere. Which is just hideous.
- I could hack run time type checking using the ctsr info in "show". But again I'd have to know when to use it or use it everywhere. And it seems like a ridiculous kludge to bring to a language that has been designed for elegance.
..So what is the Haskell idiom for dealing with this??? In fact I suppose I'm asking two questions:
1. How do I re-design this program so it is safe (use class and instance maybe, abandoning use of a single data type? but I then have to have separate Lists for each type, even if they derived from a common class?)
2. How can one use compile time checking or (less good) coding practices to eliminate the possibilty of such runtime exceptions?
And come to think of it
3. is there a Haskell book which addresses design and structural problems like this one - which I would have thought was both obvious and fundamental - because of the books I've looked at so far seem to do a tolerable job. The best of them present an adequate "on rails" tour, but none of them seem to give you the tools to address issues like this one. Whereas with C++and Stroustrupp, Common Lisp and Graham, the Smalltalk book, and I Erlang and Armstrong I'd know exactly what to do. Admittedly the C++ solutions wouldn't be pretty, but anything the compiled would be safe to run (unless I went to great efforts otherwise..)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Markus Läll

On Wed, Apr 18, 2012 at 10:10 AM, umptious
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.
..So what is the Haskell idiom for dealing with this??? In fact I suppose I'm asking two questions:
1. How do I re-design this program so it is safe (use class and instance maybe, abandoning use of a single data type? but I then have to have separate Lists for each type, even if they derived from a common class?)
2. How can one use compile time checking or (less good) coding practices to eliminate the possibilty of such runtime exceptions?
I think the usual answer is to use pattern matching. As in: myFunc :: Sahpe -> Foo myFunc (Composite xs) = ... myFunc (Circle o r) = ... etc. Does this do what you want? Antoine

Idiomatic Haskell for *drawing* shapes is to represent Shapes as functions from their origin to what they draw (e.g. Bitmap). type Drawing = Pt2 -> Bitmap -- Circle needs a radius type Circle = Float -> Drawing circle :: Circle circle r = \pt -> {...} -- Rect needs width and height type Rect = Float -> Float -> Drawing rect :: Rect rect w h = \pt -> {...} Transformations like scaling work by pre-transforming the arguments uniform_scale_rect :: Float -> Rect uniform_scale_rect sz = \w h -> rect (sz*w) (sz*h) uniform_scale_scale :: Float -> Circle uniform_scale_scale sz = \r -> cicle (sz*r) If you want a polymorphic scale function you will have to make your shapes individual newtypes so us can write specific instances for them. This works very well for drawing, but because Shapes are represented as functions they cannot support introspection e.g. querying a circle for its radius. Depending how you design your editor you might find introspection wasn't a genuine requirement.

Further to my last point - introspection is "controversial" for Shapes if you have a concrete representation anyway: If you want to make an ellipse you can non-uniformly scale a circle[*], but if you only have a query for radius you can't do edge detection on an ellipse; you might end up needing to store radius plus a list of all the affine transformations you have applied. [*] There is also the problem that a circle isn't a circle once it has been non-uniformly scaled...

On Wed, Apr 18, 2012 at 8:10 AM, umptious
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)
participants (6)
-
Antoine Latter
-
Lyndon Maydwell
-
Markus Läll
-
Stephen Tetley
-
Tim Perry
-
umptious