Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  For most geometric algorithms (e.g. Graham Scan) sorting the
      points & not using trig functions is usually better. (KC)
   2. Re:  Imperfect Graham Scan (Zhi-Qiang Lei)


----------------------------------------------------------------------

Message: 1
Date: Mon, 9 Jan 2012 13:28:58 -0800
From: KC <kc1...@gmail.com>
Subject: [Haskell-beginners] For most geometric algorithms (e.g.
        Graham Scan) sorting the points & not using trig functions is usually
        better.
To: Beginners@haskell.org
Message-ID:
        <CAMLKXy=3syre56petcoouhelhd5-m21zermqqa+bqwpemkj...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Often you sort the points to find a boundary point (extremal point).

Using trig functions burns a lot of CPU cycles so if one can use the
inner product, etc. so much the better.

-- 
--
Regards,
KC



------------------------------

Message: 2
Date: Tue, 10 Jan 2012 18:16:05 +0800
From: Zhi-Qiang Lei <zhiqiang....@gmail.com>
Subject: Re: [Haskell-beginners] Imperfect Graham Scan
To: Haskell Beginer <beginners@haskell.org>
Message-ID: <4237de64-ab87-4095-a46d-309a5fe9b...@gmail.com>
Content-Type: text/plain; charset="us-ascii"

I think I find what the problem is:

When calculating the distance in cosine function, a sqrt is missing.
There is no pivot append to the sorted list of points in sort'.
The algorithm which scan implement is incorrect. Read more details in my 
comments.

I appreciate you all.

=== prop_scan_idempotent on GrahamScan_qc.hs:8 ===
+++ OK, passed 100 tests.

=== 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) / distance where
    distance = sqrt $ (x2 - x1) ^ 2 + (y2 - y1) ^ 2

instance Ord Vector where
    compare a b = compare (f a) (f b) where
        f = negate . cosine

-- After sorting a pivot should be append to the sorted list impermanently.
-- Otherwise the last point could not be examine.
sort' :: [Point] -> [Point]
sort' xs = pivot : fmap end sortedVectors ++ [pivot] where
    sortedVectors   = sort . fmap (Vector pivot) . delete pivot $ xs
    pivot           = minimum xs

isCounterClockwise :: Point -> Point -> Point -> Bool
isCounterClockwise (Point x1 y1) (Point x2 y2) (Point x3 y3) = (x2 - x1) * (y3 
- y1) > (y2 - y1) * (x3 - x1)

-- When a point is considered clockwise or collinear, just removing it
-- is not enough, the point before it has to be re-examined. Or else,
-- the function is not idempotent. This is not mentioned on Wikipedia.
scan' :: ([Point], [Point]) -> ([Point], [Point])
scan' (p1 : p2 : p3 : xs, ys)
    | isCounterClockwise p1 p2 p3   = scan' (p2 : p3 : xs, ys ++ [p1])
    | otherwise                     = scan' (last ys : p1 : p3 : xs, init ys)
scan' (xs, ys) = ([], ys ++ xs)

-- The last point is pivot, ignore it in result.
scan :: [Point] -> [Point]
scan xs = init . (\(_, ys) -> ys) . scan' $ (xs, [])

grahamScan :: [Point] -> [Point]
grahamScan xs@(_ : _ : _ : _) = scan . sort' . nub $ xs
=== Code ===

Best regards,
Zhi-Qiang Lei
zhiqiang....@gmail.com

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120110/38d5ecd6/attachment-0001.htm>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 43, Issue 13
*****************************************

Reply via email to