
Hi Michael, On 03/09/10 01:21, Michael Litchard wrote:
Below is my solution for the Graham Scan Algorithm. I tried to limit myself to information in the first three chapters while completing this problem. Now, I want to remove the explicit recursion and use more idiomatic Haskell. I'd like to get some advice on which functions/modules would be helpful in this.
This is not really what you ask for, but I thought I would point out that you code seems to have either a bug or it doesn't implement the Graham Scan algorithm correctly. For example, when we change the points to [(10,0), (10,1),(-10,1),(-10,0),(-7,0),(-10,2),(-10,3),(-4,1),(-2,2),(-12,1)] your code gives as the solution: *Main> main [(10.0,0.0),(10.0,1.0),(-10.0,1.0),(-10.0,0.0),(-7.0,0.0),(10.0,1.0),(-4.0,1.0)] while the correct solution has only 5 points [(-10,0),(10,0),(10,1),(-10,3),(-12,1)] Yo can see my solution to this exercise at http://angel-de-vicente.blogspot.com/2010/06/graham-scan-in-haskell.html Cheers, Ángel de Vicente
<code> 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 [b] = [b] insert (b:c:cs) | (myCoTan a b)>= (myCoTan a c) = b : insert (c:cs) | otherwise = c : insert (b:cs) where myCoTan :: PointXY -> PointXY -> Double myCoTan p1 p2 = (fst p2 - fst p1) / (snd p2 - snd p1)
createHull :: [PointXY] -> [PointXY] createHull (a:b:c:cs) = a : filterPoint (createHull (b:c:cs)) where filterPoint :: [PointXY] -> [PointXY] filterPoint (x:y:z:zs) | calcTurn x y z == (DLeft) = [x] ++ [y] ++ [z] ++ filterPoint (zs) | otherwise = [x] ++ [z] ++ filterPoint (zs) filterPoint [x] = a:[x] filterPoint _ = [] createHull _ = []
main :: IO () main = do let points = [(5.0,0.0),(5.0,6.0),(3.0,-4.2),(0.0,6.0)] print $ createHull points _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- http://www.iac.es/galeria/angelv/ High Performance Computing Support PostDoc Instituto de Astrofísica de Canarias --------------------------------------------------------------------------------------------- ADVERTENCIA: Sobre la privacidad y cumplimiento de la Ley de Protección de Datos, acceda a http://www.iac.es/disclaimer.php WARNING: For more information on privacy and fulfilment of the Law concerning the Protection of Data, consult http://www.iac.es/disclaimer.php?lang=en