[Haskell-cafe] Need feedback on my Haskell code

Felipe Lessa felipe.lessa at gmail.com
Tue Jul 28 10:24:34 EDT 2009


Small tips:

- Use swap and avoid those if's.
- [a] ++ b  is the same as  a : b.
- Factor out the first point that is always there.
- Factor out line' arguments that don't change with the recursion.

Untested:

> swap :: Bool -> (a,a) -> (a,a)
> swap False = id
> swap True  = \(x,y) -> (y,x)
>
> line :: Point -> Point -> [Point]
> line (xa,ya) (xb,yb) = line' p1 p2 deltax deltay ystep isSteep 0
>   where
>     isSteep = abs (yb - ya) > abs (xb - xa)
>     (p1,p2) = let a = swap isSteep (xa,ya)
>                   b = swap isSteep (xb,yb)
>               in swap (fst a > fst b) (a, b)
>     ((x1,y1),(x2,y2)) = (p1,p2)
>     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' p1 (x2,_) deltax deltay ystep isSteep = go p1
>   where
>     go (x1,y1) error = swap isSteep (x1,y1) : rest
>         where
>           rest = if x1 == x2 then [] else go (newX,newY) newError
>           newX = x1 + 1
>           tempError = error + deltay
>           (newY, newError) = if (2*tempError) >= deltax
>                              then (y1+ystep,tempError-deltax) else (y1,tempError)


But now that we got here, you may inline line' and avoid "swap
isSteep".  I've also changed some names to more pleasant one (for
me, at least :).  Untested as well:

> swap :: Bool -> (a,a) -> (a,a)
> swap False = id
> swap True  = \(x,y) -> (y,x)
>
> line :: Point -> Point -> [Point]
> line (xa,ya) (xb,yb) = go (x1,y1) 0
>   where
>     ((x1,y1),(x2,y2)) = let a = adjust (xa,ya)
>                             b = adjust (xb,yb)
>                         in swap (fst a > fst b) (a, b)
>     adjust = swap $ abs (yb - ya) > abs (xb - xa)
>     deltax = x2 - x1
>     deltay = abs (y2 - y1)
>     ystep  = if y1 < y2 then 1 else -1
>
>     go (x,y) error =
>         let error'  = error + deltay
>             (yd,ed) = if 2*tempError >= deltax then (ystep,deltax) else (0,0)
>         in adjust (x,y) : if x == x2 then [] else go (x+1,y+yd) (error' - ed)

HTH,

--
Felipe.


More information about the Haskell-Cafe mailing list