
Thanks Neil,
That helped. Now the code looks better - I still feel a little bad about the way I repeat calls to line' though - I was thinking of using a partially applied function with (newX,newY) as the last parameter - but that'll make the code less readable.
line :: Point -> Point -> [Point]
line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0
where
isSteep = abs (yb - ya) > abs (xb - xa)
(xa',ya',xb',yb') = if isSteep
then (ya,xa,yb,xb)
else (xa,ya,xb,yb)
(x1,y1,x2,y2) = if xa' > xb'
then (xb',yb',xa',ya')
else (xa',ya',xb',yb')
deltax = x2 - x1
deltay = abs (y2 - y1)
ystep = if y1 < y2 then 1 else -1
line' (x1, y1) (x2, y2) deltax deltay ystep isSteep error
| x1 == x2 = if isSteep then [(y1, x1)] else [(x1, y1)]
| isSteep =
(y1, x1) :
line' (newX, newY) (x2, y2) deltax deltay ystep isSteep newError
| otherwise =
(x1, y1) :
line' (newX, newY) (x2, y2) deltax deltay ystep isSteep newError
where newX = x1 + 1
tempError = error + deltay
(newY, newError)
= if (2 * tempError) >= deltax then
(y1 + ystep, tempError - deltax) else (y1, tempError)
Regards,
Kashyap
________________________________
From: Neil Mitchell
Hi Everyone, I managed to write up the line drawing function using the following links - http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell
line :: Point -> Point -> [Point] line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0 where isSteep = abs (yb - ya) > abs (xb - xa) (xa',ya',xb',yb') = if isSteep then (ya,xa,yb,xb) else (xa,ya,xb,yb) (x1,y1,x2,y2) = if xa' > xb' then (xb',yb',xa',ya') else (xa',ya',xb',yb') deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 < y2 then 1 else -1
line' :: Point -> Point -> Integer -> Integer -> Integer -> Bool -> Integer -> [Point] line' (x1,y1) (x2,y2) deltax deltay ystep isSteep error = if x1 == x2 then if isSteep then [(y1,x1)] else [(x1,y1)] else if isSteep then [(y1,x1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep newError else [(x1,y1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep newError where newX = x1 + 1 tempError = error + deltay (newY, newError) = if (2*tempError) >= deltax then (y1+ystep,tempError-deltax) else (y1,tempError)
Can someone please provide feedback on this? In terms of, how do I get more Haskell'ism into it.
Regards, Kashyap
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe