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

Michael Litchard michael at schmong.org
Mon Jan 19 03:32:24 EST 2009


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


sortListByCoTangent :: [PointXY] -> [PointXY]
sortListByCoTangent [] = []
sortListByCoTangent [a] = [a]
sortListByCoTangent (a:as) = a : insert (sortListByCoTangent as)
                 where insert :: [PointXY] -> [PointXY]
                       insert [] = [a]
                       insert [b] = [b]
                       insert (b:c:cs) | (myCoTan a b) >= (myCoTan a
c) =  b : c : cs
                                       | otherwise
 =  c : b : insert 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.

I appreciate any help/hints


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.


More information about the Haskell-Cafe mailing list