[Haskell-cafe] Graham-Scan Algorithm exercise from Chapter 3 Real World Haskell

Daniel Fischer daniel.is.fischer at web.de
Mon Jan 19 05:03:15 EST 2009


Am Montag, 19. Januar 2009 10:17 schrieb Daniel Fischer:
> Am Montag, 19. Januar 2009 09:32 schrieb Michael Litchard:
> > I have started the Graham Scan Algorithm exercise. I'm getting tripped
> > up by the sortByCotangent* function.
> > Here's what I have so far
> >
> > data Direction = DStraight
> >
> >                | DLeft
> >                | DRight
> >
> >                  deriving (Eq,Show)
> > type PointXY = (Double,Double)
> >
> > calcTurn :: PointXY -> PointXY -> PointXY -> Direction
> > calcTurn a b c
> >
> >         | crossProduct == 0 = DStraight
> >         | crossProduct > 0  = DLeft
> >         | otherwise         = DRight
> >
> >        where crossProduct = ((fst b - fst a) * (snd c - snd a)) -
> > ((snd b - snd a) * (fst c - fst a))
> >
> >
> > calcDirectionList :: [PointXY] -> [Direction]
> > calcDirectionList (x:y:z:zs) = (calcTurn x y z) : (calcDirectionList
> > (y:z:zs)) calcDirectionList _ = []
> >
> > sortListByY :: [PointXY] -> [PointXY]
> > sortListByY [] = []
> > sortListByY [a] = [a]
> > sortListByY (a:as) = insert (sortListByY as)
> >            where insert [] = [a]
> >                  insert (b:bs) | snd a <= snd b = a : b : bs
> >
> >                                | otherwise      = b : insert bs
>
> I think it would be easier to see what the code does if you had it
>
> sortListByY [] = []
> sortListByY (a:as) = insertByY a (sortListByY as)
>       where
> 	insertByY a (b:bs)
>
> 	    | snd a <= snd b = a:b:bs
> 	    | otherwise = b:insertByY a bs
>
> 	insertByY a [] = [a]
>
> analogously for sortListByCoTangent.
>
> > sortListByCoTangent :: [PointXY] -> [PointXY]
> > sortListByCoTangent [] = []
> > sortListByCoTangent [a] = [a]
> > sortListByCoTangent (a:as) = a : insert (sortListByCoTangent as)
> >                  where insert :: [PointXY] -> [PointXY]
> >                        insert [] = [a]
>
> 			^^^^^^^^^^^^^^
> shouldn't that be insert [] = [], if at all? However, this will never be
> encountered, so you can delete it.
>
> >                        insert [b] = [b]
> >                        insert (b:c:cs) | (myCoTan a b) >= (myCoTan a
> > c) =  b : c : cs
> >
> >                                        | otherwise
> >
> >  =  c : b : insert cs
>
> There's the oops. You can only pass one point at a time, so it should be
> ... b:insert (c:cs)
> resp.
> ... c:insert (b:cs)
>
> >                              where myCoTan :: PointXY -> PointXY ->
> > Double myCoTan p1 p2 = (fst p2 - fst p1) / (snd p2 - snd p1)
> >
> > test data
> > *Main> sortListByCoTangent (sortListByY
> > [(1,2),(2,6),(3,10),(4,9),(5,10),(2,20),(6,15)])
> > [(1.0,2.0),(5.0,10.0),(2.0,6.0),(4.0,9.0),(6.0,15.0),(3.0,10.0),(2.0,20.0
> >)]
> >
> > (1,0,2.0) is correct. That's the pivot point. It screws up from there.
> >
> > I suspect my insert is hosed, but I'm having difficulty analyzing the
> > logic of the code. I'd like hints/help but with the following
> > boundaries.
> >
> > (1) I want to stick with the parts of the language that's been
> > introduced in the text so far. I know there are solutions that make
> > this problem trivial, however using those misses the point.
> > (2) I'd prefer going over the logic of my code, versus what is
> > supposed to happen. I'm trying to learn how to troubleshoot haskell
> > code, more than implement the graham scan algorithm.
>
> Walk through your code by hand for very small inputs (say four or five
> vertices in several orders). Then you see how exactly it works, and find
> more easily what's wrong (and what to rewrite in a clearer fashion).
>
> > I appreciate any help/hints

Another thing, your sortListByCoTangent is inefficient because you 
unnecessarily sort all tails of the list according to their first element, 
while you only want to sort according to the very first element of the entire 
list. Also, you recompute the cotangent of all segments, it would probably be 
better to calculate it only once.

sortListByCoTangent [] = []
sortListByCoTangent [a] = [a]
sortListByCoTangent (a:bs) = a:map point (sortBC (map addCT bs))
      where
	addCT b = (fst b - fst a, snd b - snd a, b)
	point (dx,dy,p) = p
	sortBC [] = []
	sortBC (t:ts) = insert t (sortBC ts)
	insert t [] = [t]
	insert (dx1,dy1,p1) ((dx2,dy2,p2):ts)
	    | dx1*dy2 < dx2*dy1 = (dx2,dy2,p2):insert (dx1,dy1,p1) ts
	    | otherwise = (dx1,dy1,p1):(dx2,dy2,p2):ts

sorts only once. However, it is still an insertion sort, which is not the most 
efficient sorting method.
> >
> >
> > Michael Litchard
> >
> > *It seems the wikipedia page on the graham scan algorithm is wrong
> > concerning the following part of the algorithm.
> > "...instead, it suffices to calculate the tangent of this angle, which
> > can be done with simple arithmetic."
> > Someone from #haskell said that it's the cotangent I want, and my math
> > tutor confirmed. If this is the case, I suppose we should submit a
> > correction.
>
> Actually, both will do. Using the tangent requires a little sophistication
> in sorting, though (first positive tangent in increasing order, then
> infinity if it appears, finally negative tangent in decreasing order), so

Oops, negative tangents also in increasing order, of course. Need more sleep.

> it's not technically wrong, but the cotangent is better.



More information about the Haskell-Cafe mailing list