[Haskell-beginners] Imperfect Graham Scan

Ray Song emacsray at gmail.com
Sun Jan 8 16:54:13 CET 2012


The 'scan' is flawed. A counterwise angle formed by the first three points
does not guarantee p1's existence in the hull.
2012-1-8 下午3:32 於 "Zhi-Qiang Lei" <zhiqiang.lei at gmail.com> 寫道:
>
> Hi,
>
> The Graham Scan function I wrote, looks like running well. But when I put
it in QuickCheck, it just failed in some case. Anyone can show me some
clues about the problem? Thanks.
>
> When I test it in ghci with some example, it returns the right result.
> *Main> let xs = [Point {x = 1.0, y = 1.0},Point {x = 0.0, y = 4.0},Point
{x = 0.0, y = 6.0},Point {x = 3.0, y = 5.0},Point {x = 4.0, y = 4.0},Point
{x = 4.0, y = 1.0},Point {x = 3.0, y = 3.0},Point {x = 2.0, y = 2.0},Point
{x = 5.0, y = 5.0}]
> *Main> grahamScan xs
> [Point {x = 1.0, y = 1.0},Point {x = 4.0, y = 1.0},Point {x = 5.0, y =
5.0},Point {x = 0.0, y = 6.0},Point {x = 0.0, y = 4.0}]
> *Main> grahamScan it
> [Point {x = 1.0, y = 1.0},Point {x = 4.0, y = 1.0},Point {x = 5.0, y =
5.0},Point {x = 0.0, y = 6.0},Point {x = 0.0, y = 4.0}]
>
> However, QuickCheck find some points which can fail it. Could it be a
data type overflow problem?
>
> prop_scan_idempotent xs = not (null xs) ==> (grahamScan . grahamScan) xs
== grahamScan xs
>
> *Main> quickCheck prop_scan_idempotent
> *** Failed! Falsifiable (after 13 tests and 4 shrinks):
> [Point {x = -6.29996952110807, y = -91.37172300100718},Point {x =
9.353314917365527, y = 64.35532141764591},Point {x = -23.826685687218355, y
= 60.32049750442556},Point {x = -1.4281411275074123, y =
31.54197550020998},Point {x = -2.911218918860731, y = 15.564623822256719}]
>
> === code ===
> module GrahamScan (grahamScan, Point(..))
> where
>
> import Data.List
> import Data.Ratio
>
> data Point = Point {
>    x :: Double,
>    y :: Double
> } deriving (Eq, Show)
>
> instance Ord Point where
>    compare (Point x1 y1) (Point x2 y2) = compare (y1, x1) (y2, x2)
>
> data Vector = Vector {
>    start   :: Point,
>    end     :: Point
> } deriving (Eq)
>
> cosine :: Vector -> Double
> cosine (Vector (Point x1 y1) (Point x2 y2)) = (x2 - x1) / ((x2 - x1) ^ 2
+ (y2 - y1) ^ 2)
>
> instance Ord Vector where
>    compare a b = compare (f a) (f b) where
>        f = negate . cosine
>
> sort' :: [Point] -> [Point]
> sort' xs = pivot : fmap end sortedVectors where
>    sortedVectors   = sort . fmap (Vector pivot) . delete pivot $ xs
>    pivot           = minimum xs
>
> counterClockwise :: Point -> Point -> Point -> Bool
> counterClockwise (Point x1 y1) (Point x2 y2) (Point x3 y3) = (x2 - x1) *
(y3 - y1) > (y2 - y1) * (x3 - x1)
>
> scan :: [Point] -> [Point]
> scan (p1 : p2 : p3 : xs)
>    | counterClockwise p1 p2 p3 = p1 : scan (p2 : p3 : xs)
>    | otherwise                 = scan (p1 : p3 : xs)
> scan xs = xs
>
> grahamScan :: [Point] -> [Point]
> grahamScan = scan . sort' . nub
> === code ===
>
>
> Best regards,
> Zhi-Qiang Lei
> zhiqiang.lei at gmail.com
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20120108/12d25944/attachment.htm>


More information about the Beginners mailing list