Need feedback on my Haskell code
 
            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
 
            Hi Kashyap,
My first suggestion would be to run HLint over the code
(http://community.haskell.org/~ndm/hlint) - that will spot a few easy
simplifications.
Thanks
Neil
On Tue, Jul 28, 2009 at 2:04 PM, CK Kashyap
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
 
            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
 
            CK Kashyap 
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)
It's early in my day, so I'm not very awake, but this looks like it could be an iterate or something like that, rather than explicit recursion. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
 
            On Tue, Jul 28, 2009 at 3:04 PM, CK Kashyap
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
I tried to simplify your function a little bit : line :: Point -> Point -> [Point] line pa@(xa,ya) pb@(xb,yb) = map maySwitch . unfoldr go $ (x1,y1,0) where steep = abs (yb - ya) > abs (xb - xa) maySwitch = if steep then (\(x,y) -> (y,x)) else id [(x1,y1),(x2,y2)] = sort [maySwitch pa, maySwitch pb] deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 < y2 then 1 else -1 go (xTemp, yTemp, error) | xTemp > x2 = Nothing | otherwise = Just ((xTemp, yTemp), (xTemp + 1, newY, newError)) where tempError = error + deltay (newY, newError) = if (2*tempError) >= deltax then (yTemp+ystep,tempError-deltax) else (yTemp,tempError) I think it will be a bit better, tell me what you think ? -- Jedaï
 
            Thank you very much Jedai ... this looks much more concise and does not contain the repetitions that I had. I'd need to go over it more to understand it better.
I'll ping you if I have any questions about this.
Regards,
Kashyap
________________________________
From: Chaddaï Fouché 
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
I tried to simplify your function a little bit : line :: Point -> Point -> [Point] line pa@(xa,ya) pb@(xb,yb) = map maySwitch . unfoldr go $ (x1,y1,0) where steep = abs (yb - ya) > abs (xb - xa) maySwitch = if steep then (\(x,y) -> (y,x)) else id [(x1,y1),(x2,y2)] = sort [maySwitch pa, maySwitch pb] deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 < y2 then 1 else -1 go (xTemp, yTemp, error) | xTemp > x2 = Nothing | otherwise = Just ((xTemp, yTemp), (xTemp + 1, newY, newError)) where tempError = error + deltay (newY, newError) = if (2*tempError) >= deltax then (yTemp+ystep,tempError-deltax) else (yTemp,tempError) I think it will be a bit better, tell me what you think ? -- Jedaï
 
            It worked like a charm!!! I'd need more time to get my head around "unfoldr"
I'd appreciate it very much if you could explain this line  "map maySwitch . unfoldr go $ (x1,y1,0)"
I did not fully understand the "$" in that line - I tried putting parenthesis in various places to get rid of "$" but did not seem to work.
Regards,
Kashyap
________________________________
From: Chaddaï Fouché 
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
I tried to simplify your function a little bit : line :: Point -> Point -> [Point] line pa@(xa,ya) pb@(xb,yb) = map maySwitch . unfoldr go $ (x1,y1,0) where steep = abs (yb - ya) > abs (xb - xa) maySwitch = if steep then (\(x,y) -> (y,x)) else id [(x1,y1),(x2,y2)] = sort [maySwitch pa, maySwitch pb] deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 < y2 then 1 else -1 go (xTemp, yTemp, error) | xTemp > x2 = Nothing | otherwise = Just ((xTemp, yTemp), (xTemp + 1, newY, newError)) where tempError = error + deltay (newY, newError) = if (2*tempError) >= deltax then (yTemp+ystep,tempError-deltax) else (yTemp,tempError) I think it will be a bit better, tell me what you think ? -- Jedaï
 
            On Wed, Jul 29, 2009 at 12:04 PM, CK Kashyap 
It worked like a charm!!! I'd need more time to get my head around "unfoldr" I'd appreciate it very much if you could explain this line "map maySwitch . unfoldr go $ (x1,y1,0)" I did not fully understand the "$" in that line - I tried putting parenthesis in various places to get rid of "$" but did not seem to work.
(map maySwitch . unfoldr go) (x1,y1,0) should work. Cheers, Johan
 
            On Wed, Jul 29, 2009 at 4:06 AM, Johan Tibell
(map maySwitch . unfoldr go) (x1,y1,0)
should work.
which is the same as
map maySwitch (unfoldr go (x1,y1,0))
People have stylistic differences with ($) vs. (.); I would write it as
map maySwitch $ unfoldr go $ (x1,y1,0) (or, more likely) map maySwitch $ unfoldr go (x1,y1,0)
but some people like to make the function pipelines more explicit (with the composition operator (.) instead of the application operator ($)). Read ($) as a parenthesis that extends as far to the right as possible; so you can write, for example:
map (+1) $ map (*2) $ map (+3) [1,2,3] which is the same as map (+1) (map (*2) (map (+3) [1,2,3])) but without having to count how many parentheses you need on the right.
Due to the precedences of (.) and ($), you can use either
blah $ blah2 $ blah3 $ something or blah . blah2 . blah3 $ something
After inlining ($) and (.), the former is
blah (blah2 (blah3 (something))) whereas the latter is (\x -> blah ((\y -> blah2 (blah3 y)) x)) (something) which beta reduces to the same thing: => blah ((\y -> blah2 (blah3 y)) (something)) => blah (blah2 (blah3 (something)))
-- ryan
 
            On Fri, Jul 31, 2009 at 5:53 AM, Ryan Ingram
Read ($) as a parenthesis that extends as far to the right as possible; so you can write, for example:
That doesn't always work, for example : map (+2) . map (*1) $ [1,2,3] = [4,6,8] Now replacing the $ by a parenthesis that extends as far to the right as possible : map (+2) . map (*1) ( [1,2,3] ) <interactive>:1:11: Couldn't match expected type `a -> [a1]' against inferred type `[a2]' In the second argument of `(.)', namely `map (* 2) ([1, 2, 3])' In the expression: map (+ 2) . map (* 2) ([1, 2, 3]) In the definition of `it': it = map (+ 2) . map (* 2) ([1, 2, 3])
 
            I personally find 
map maySwitch (unfoldr go (x1,y1,0)) and map maySwitch $ unfoldr go (x1,y1,0) more intuitive.
I can read it as map the maySwitch function over the list generated from the unfolding.
Is there any difference in the evaluation steps between the composition version and the non-composition version?
Regards,
Kashyap
________________________________
From: david48 
Read ($) as a parenthesis that extends as far to the right as possible; so you can write, for example:
That doesn't always work, for example : map (+2) . map (*1) $ [1,2,3] = [4,6,8] Now replacing the $ by a parenthesis that extends as far to the right as possible : map (+2) . map (*1) ( [1,2,3] ) <interactive>:1:11: Couldn't match expected type `a -> [a1]' against inferred type `[a2]' In the second argument of `(.)', namely `map (* 2) ([1, 2, 3])' In the expression: map (+ 2) . map (* 2) ([1, 2, 3]) In the definition of `it': it = map (+ 2) . map (* 2) ([1, 2, 3])
 
            On Fri, Jul 31, 2009 at 2:12 PM, CK Kashyap
I personally find map maySwitch (unfoldr go (x1,y1,0)) and map maySwitch $ unfoldr go (x1,y1,0) more intuitive.
I can read it as map the maySwitch function over the list generated from the unfolding.
Is there any difference in the evaluation steps between the composition version and the non-composition version?
There may be small differences in the result after optimisation but you shouldn't worry about that right now (if you really want to optimise this function, the first thing to do is to change your data structure for points : a strict pair of int (data Point = P !Int !Int) could easily go more than 5 times faster, I tried). I tend to always use this "map maySwitch . unfoldr go $ (x1,y1,0)" style since I like to see things in terms of functions compositions and it is easier to refactor this kind of code with copy and paste (not really relevant here but for longer chains it's interesting). -- Jedaï
 
            On Wed, Jul 29, 2009 at 12:04 PM, CK Kashyap
map maySwitch . unfoldr go $ (x1,y1,0)
I'm not an expert and I might say things the wrong way or without the required rigor, so with this disclaimer here's my explanation : go calculates a step of the line, given the current coordinates and the error value it returns nothing if the line is done. unfoldr go calculates a list of lines coordinates, keeping calling go, and stopping when go returns nothing. maySwitch takes a coordinate, and switches the x and y values depending on the axis we're following map maySwitch does the same for the entire list of coordinates. when you compose the two, map maySwitch . unfoldr go is then a function that takes initial coordinates, makes a list of coordinates and may switch the x's and y's depending on the axis we're following. Now (.) takes two functions, namely map maySwitch and unfoldr go. If you don't write the $, what you actually mean is (map maySwitch) . ( unfoldr go (x1,y1,0)) this ( unfoldr go (x1,y1,0)) is not of the right type for (.) : it should take a parameter and return a value, but here it just returns a value. so you have to find a way to give (x1,y1,0) to the whole composed function map maySwitch . unfoldr go. the obvious way to do it is by writing: ( map maySwitch . unfoldr go ) (x1,y1,0 ) the $ is just a more readable way to write it : since $ binds with less priority, in map maySwitch . unfoldr go $ (x1,y1,0) what's on the right of $ will be applied to what's on the left David.
 
            Thanks David 
Regards,
Kashyap
________________________________
From: david48 
map maySwitch . unfoldr go $ (x1,y1,0)
I'm not an expert and I might say things the wrong way or without the required rigor, so with this disclaimer here's my explanation : go calculates a step of the line, given the current coordinates and the error value it returns nothing if the line is done. unfoldr go calculates a list of lines coordinates, keeping calling go, and stopping when go returns nothing. maySwitch takes a coordinate, and switches the x and y values depending on the axis we're following map maySwitch does the same for the entire list of coordinates. when you compose the two, map maySwitch . unfoldr go is then a function that takes initial coordinates, makes a list of coordinates and may switch the x's and y's depending on the axis we're following. Now (.) takes two functions, namely map maySwitch and unfoldr go. If you don't write the $, what you actually mean is (map maySwitch) . ( unfoldr go (x1,y1,0)) this ( unfoldr go (x1,y1,0)) is not of the right type for (.) : it should take a parameter and return a value, but here it just returns a value. so you have to find a way to give (x1,y1,0) to the whole composed function map maySwitch . unfoldr go. the obvious way to do it is by writing: ( map maySwitch . unfoldr go ) (x1,y1,0 ) the $ is just a more readable way to write it : since $ binds with less priority, in map maySwitch . unfoldr go $ (x1,y1,0) what's on the right of $ will be applied to what's on the left David.
 
            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.
participants (8)
- 
                 Chaddaï Fouché Chaddaï Fouché
- 
                 CK Kashyap CK Kashyap
- 
                 david48 david48
- 
                 Felipe Lessa Felipe Lessa
- 
                 Johan Tibell Johan Tibell
- 
                 Jon Fairbairn Jon Fairbairn
- 
                 Neil Mitchell Neil Mitchell
- 
                 Ryan Ingram Ryan Ingram