Area from [(x,y)] using foldl

Here's an (Fortran) algorithm for calculating an area, given one dimensional arrays of Xs and Ys. I wrote a recursive Haskell function that works, and one using FOLDL that doesn't. Why would Haskell be "expecting" (t, t) out of ((*) (xold-x) (yold+y))? Michael ==================== AREA = 0.0 XOLD = XVERT(NVERT) YOLD = YVERT(NVERT) DO 10 N = 1, NVERT X = XVERT(N) Y = YVERT(N) AREA = AREA + (XOLD - X)*(YOLD + Y) XOLD = X YOLD = Y 10 CONTINUE AREA = 0.5*AREA ==================== area :: [(Double,Double)] -> Double area ps = abs $ (/2) $ area' (last ps) ps where area' _ [] = 0 area' (x0,y0) ((x,y):ps) = (x0-x)*(y0+y) + area' (x,y) ps *Main> let p = [(0.0,0.0),(1.0,0.0),(1.0,1.0),(0.0,1.0),(0.0,0.0)] *Main> area (last p) p 1.0 *Main> ==================== area :: [(Double,Double)] -> Double area p = foldl (\ (xold,yold) (x,y) -> ((*) (xold-x) (yold+y))) 0 ((last p):p) Prelude> :l area [1 of 1] Compiling Main ( area.hs, interpreted ) area.hs:29:40: Occurs check: cannot construct the infinite type: t = (t, t) Expected type: (t, t) Inferred type: t In the expression: ((*) (xold - x) (yold + y)) In the first argument of `foldl', namely `(\ (xold, yold) (x, y) -> ((*) (xold - x) (yold + y)))' Failed, modules loaded: none. Prelude>

The type of foldl is:
(b -> a -> b) -> b -> [a] -> b
What do you expect 'a' and 'b' to be in your algorithm?
2009/11/8 michael rice
Here's an (Fortran) algorithm for calculating an area, given one dimensional arrays of Xs and Ys. I wrote a recursive Haskell function that works, and one using FOLDL that doesn't. Why would Haskell be "expecting" (t, t) out of ((*) (xold-x) (yold+y))?
Michael
====================
AREA = 0.0 XOLD = XVERT(NVERT) YOLD = YVERT(NVERT) DO 10 N = 1, NVERT X = XVERT(N) Y = YVERT(N) AREA = AREA + (XOLD - X)*(YOLD + Y) XOLD = X YOLD = Y 10 CONTINUE
AREA = 0.5*AREA
====================
area :: [(Double,Double)] -> Double area ps = abs $ (/2) $ area' (last ps) ps where area' _ [] = 0 area' (x0,y0) ((x,y):ps) = (x0-x)*(y0+y) + area' (x,y) ps
*Main> let p = [(0.0,0.0),(1.0,0.0),(1.0,1.0),(0.0,1.0),(0.0,0.0)] *Main> area (last p) p 1.0 *Main>
====================
area :: [(Double,Double)] -> Double area p = foldl (\ (xold,yold) (x,y) -> ((*) (xold-x) (yold+y))) 0 ((last p):p)
Prelude> :l area [1 of 1] Compiling Main ( area.hs, interpreted )
area.hs:29:40: Occurs check: cannot construct the infinite type: t = (t, t) Expected type: (t, t) Inferred type: t In the expression: ((*) (xold - x) (yold + y)) In the first argument of `foldl', namely `(\ (xold, yold) (x, y) -> ((*) (xold - x) (yold + y)))' Failed, modules loaded: none. Prelude>
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

Of course! Back to the drawing board.
Thanks,
Michael
--- On Sun, 11/8/09, Eugene Kirpichov

On Sun, Nov 8, 2009 at 9:04 PM, michael rice
Of course! Back to the drawing board.
If I understand the problem correctly, I'm not convinced that foldl is the right approach (nevermind that foldl is almost never what you want, foldl' and foldr being the correct choice almost always). My proposition would be the following :
area ps = abs . (/2) . sum $ zipWith (\(x,y) (x',y') -> (x - x') * (y + y')) ps (tail $ cycle ps)
I think it express the algorithm more clearly. -- Jedaï

That's certainly better than mine, but I'm lost again, with the following. What seemed like a simple improvement doesn't compile.
Michael
===============
This works.
area :: [(Double,Double)] -> Double
area ps = abs $ (/2) $ area' (last ps) ps
where area' _ [] = 0
area' (x0,y0) ((x,y):ps) = (x0-x)*(y0+y) + area' (x,y) ps
*Main> let p = [(0.0,0.0),(1.0,0.0),(1.0,1.0),(0.0,1.0),(0.0,0.0)]
*Main> area (last p) p
1.0
*Main>
===============
This doesn't.
area :: [(Double,Double)] -> Double
area p = abs $ (/2) $ area' (last p):p
where area' [] = 0
area' ((x0,y0),(x,y):ps) = ((x0-x)*(y0+y)) + area' (x,y):ps
--- On Sun, 11/8/09, Chaddaï Fouché
area ps = abs . (/2) . sum $ zipWith (\(x,y) (x',y') -> (x - x') * (y + y')) ps (tail $ cycle ps)
I think it express the algorithm more clearly. -- Jedaï

I see what one problem is, what happens when I end up with (x,y):[]? However, I'm confused about how Haskell is "expecting" and "inferring" upon compilation.
Michael
--- On Sun, 11/8/09, michael rice
area ps = abs . (/2) . sum $ zipWith (\(x,y) (x',y') -> (x - x') * (y + y')) ps (tail $ cycle ps)
I think it express the algorithm more clearly. -- Jedaï -----Inline Attachment Follows----- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

How about these type signatures.
import Data.List
poly1 = [(0,1),(5,0),(3,4)]::[(Double,Double)]
areaPoly :: [(Double,Double)] -> Double
areaPolyCalc :: (Double,(Double,Double)) -> (Double,Double) ->
(Double,(Double,Double))

How about these BETTER type signatures.
-- Area of a Polygon
import Data.List
type X = Double
type Y = Double
type Area = Double
poly1 = [(0,1),(5,0),(3,4)]::[(X,Y)]
areaPoly :: [(X,Y)] -> Area
areaPolyCalc :: (Area,(X,Y)) -> (X,Y) -> (Area,(X,Y))

Sorry, I forgot to add that if the polygon is very far from the
origin, you may have overflow or increased round off error; it is
better to translate the polygon back to the origin, before doing the
area calculation.
How about these BETTER type signatures.
-- Area of a Polygon
import Data.List
type X = Double
type Y = Double
type Area = Double
poly1 = [(0,1),(5,0),(3,4)]::[(X,Y)]
areaPoly :: [(X,Y)] -> Area
areaPolyCalc :: (Area,(X,Y)) -> (X,Y) -> (Area,(X,Y))

Hi Casey,
I was already aware of the translation thing, but didn't want to complicate.
Lot's of ways to skin a cat. I wrote a Lispy solution, then had the feeling I could improve on it w/Haskell. Picking the right tool takes practice.
Thanks,
Michael
--- On Sun, 11/8/09, Casey Hawthorne

On Sun, 8 Nov 2009 15:07:45 -0800 (PST), you wrote:
Hi Casey,
I was already aware of the translation thing, but didn't want to complicate.
Lot's of ways to skin a cat. I wrote a Lispy solution, then had the feeling I could improve on it w/Haskell. Picking the right tool takes practice.
Thanks,
Michael
Since Haskell is a pure functional language, it adds lazy evaluation as another tool to your modularity toolbox. Lazy evaluation separates control from computation, so, if the computation of sum is going off the rails (and I don't mean Ruby on Rails), one can prematurely terminate the calculation, without evaluating more points.
--- On Sun, 11/8/09, Casey Hawthorne
wrote: From: Casey Hawthorne
Subject: Re: [Haskell-cafe] Area from [(x,y)] using foldl To: haskell-cafe@haskell.org Date: Sunday, November 8, 2009, 5:44 PM Sorry, I forgot to add that if the polygon is very far from the origin, you may have overflow or increased round off error; it is better to translate the polygon back to the origin, before doing the area calculation.
How about these BETTER type signatures.
-- Area of a Polygon import Data.List
type X = Double type Y = Double type Area = Double
poly1 = [(0,1),(5,0),(3,4)]::[(X,Y)]
areaPoly :: [(X,Y)] -> Area
areaPolyCalc :: (Area,(X,Y)) -> (X,Y) -> (Area,(X,Y))
areaPoly (pt:pts) = 0.5 * (fst (foldl' areaPolyCalc (0,pt) pts))
areaPolyCalc (sum,(x,y)) (xNext,yNext) = (sum + (x * yNext - xNext * y),(xNext,yNext))
-- Regards, Casey

On Sun, Nov 8, 2009 at 10:30 PM, michael rice
This doesn't.
area :: [(Double,Double)] -> Double area p = abs $ (/2) $ area' (last p):p
where area' [] = 0 area' ((x0,y0),(x,y):ps) = ((x0-x)*(y0+y)) + area' (x,y):ps
This function is almost correct except you got your priorities wrong : application priority is always stronger than any operator's so "area' (last p):p" is read as "(area' (last p)) : p"... Besides your second pattern is also wrong, the correct code is : area :: [(Double,Double)] -> Double area p = abs $ (/2) $ area' (last p : p) where area' ((x0,y0):(x,y):ps) = ((x0-x)*(y0+y)) + area' (x,y):ps area' _ = 0 -- Jedaï
participants (4)
-
Casey Hawthorne
-
Chaddaï Fouché
-
Eugene Kirpichov
-
michael rice