Graham Scan Implementation

From HaskellWiki
Revision as of 15:23, 27 September 2009 by Wassermanlouis (talk | contribs)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Descriptions of this problem can be found in Real World Haskell, Chapter 3

--Graham Scan exercise

--Direction type
data Direction = LeftTurn
               | RightTurn
               | Straight
                deriving (Show, Eq)

--Point type
data Point = Point (Double, Double)
             deriving (Show)

--some points
p0 = Point (2.1,2.0)
p1 = Point (4.2,2.0)
p2 = Point (0.5,2.5)
p3 = Point (3.2,3.5)
p4 = Point (1.2,4.0)
p5 = Point (0.7,4.7)
p6 = Point (1.0,1.0)
p7 = Point (3.0,5.2)
p8 = Point (4.0,4.0)
p9 = Point (3.5,1.5)
pA = Point (0.5,1.0)
points = [p0,p1,p2,p3,p4,p5,p6,p7,p8,p9,pA]

-- Actually, I'd leave it as EQ, GT, LT.  Then, actually,
-- if you wanted to sort points rotationally around a single point,
-- sortBy (dir x) would actually work. --wasserman.louis@gmail.com
--Get direction of single set of line segments
dir :: Point -> Point -> Point -> Direction
dir (Point (ax, ay)) (Point (bx, by)) (Point (cx, cy)) = case sign of
                                  EQ -> Straight
                                  GT -> LeftTurn
                                  LT -> RightTurn
                                  where sign = compare ((bx - ax) * (cy - ay) - (by - ay) * (cx - ax)) 0

--Get a list of Directions from a list of Points
dirlist :: [Point] -> [Direction]
dirlist (x:y:z:xs) = dir x y z : dirlist (y:z:xs)
dirlist _ = []

--Compare Y axes
sortByY :: [Point] -> [Point]
sortByY xs = sortBy lowestY xs
             where lowestY (Point(x1,y1)) (Point (x2,y2)) = if y1 == y2 
                                                            then compare x1 x2
                                                            else compare y1 y2
--get COT of line defined by two points and the x-axis
pointAngle :: Point -> Point -> Double
pointAngle (Point (x1, y1)) (Point (x2, y2)) = (x2 - x1) / (y2 - y1)

--compare based on point angle
pointOrdering :: Point -> Point -> Ordering
pointOrdering a b = compare (pointAngle a b) 0.0

--Sort by angle
sortByAngle :: [Point] -> [Point]
sortByAngle ps = bottomLeft : sortBy (compareAngles bottomLeft) (tail (sortedPs))
                where sortedPs = sortByY ps
                      bottomLeft = head (sortedPs)

                      

--Compare angles
compareAngles :: Point -> Point -> Point -> Ordering
compareAngles base a b = compare (pointAngle base b) (pointAngle base a)

--Graham Scan
gscan :: [Point] -> [Point]
gscan ps = scan (sortByAngle ps)
          where scan (x:y:z:xs) = if dir x y z == RightTurn 
                                  then x: scan (z:xs)
                                  else x: scan (y:z:xs)
                scan [x,y] = [x,y] -- there's no shame in a pattern match
                                   -- of this type!
                scan _ = []