Re: [Haskell-cafe] Is there a nicer way to do this?

mfeathers:
Don Stewart wrote:
mfeathers:
segment :: Int -> [a] -> [[a]] segment 0 _ = [] segment _ [] = [] segment n x = (take n x) : segment n (drop n x)
The first set of parens can go,
segment n x = take n x : segment n (drop n x)
I did a version of this which used splitAt but I wasn't sure whether it was going to buy me anything re performance that would justify its ugliness.
Besides,
splitAt n xs = (take n xs, drop n xs)
Thanks. That is odd, though. It makes me wonder what to expect re optimization. Would the compiler/runtime know that splitAt could be done in a single pass?
Not with that definition. It would require some moderately unusual fusion combining the take and drop into a single fold with the (,) on the inside, rather than on the outside. However, GHC actually implements splitAt as: splitAt (I n) ls | n < 0 = ([], ls) | otherwise = splitAt' n ls where splitAt' :: Int -> [a] -> ([a], [a]) splitAt' 0 xs = ([], xs) splitAt' _ xs@[] = (xs, xs) splitAt' m (x:xs) = (x:xs', xs'') where (xs', xs'') = splitAt' (m - 1) xs So there may be some benefit. -- Don

Decided a while ago to write some code to calculate the Mandelbrot set using the escape iterations algorithm. Discovered after mulling it about that I could just built it as an infinite list of infinite lists and then extract any rectangle of values that I wanted: type Point = (Double, Double) sq :: Double -> Double sq x = x ^ 2 translate :: Point -> Point -> Point translate (r0, i0) (r1, i1) = (r0 + r1, i0 + i1) mandel :: Point -> Point mandel (r, i) = (sq r + sq i, 2 * r * i) notEscaped :: Point -> Bool notEscaped (r, i) = (sq r + sq i) <= 4.0 trajectory :: (Point -> Point) -> [Point] trajectory pointFunction = takeWhile notEscaped $ iterate pointFunction seed where seed = (0.0, 0.0) escapeIterations :: (Point -> Point) -> Int escapeIterations = length . tail . take 1024 . trajectory mandelbrot :: Double -> [[Int]] mandelbrot incrementSize = [[ escapeIterations $ translate (x, y) . mandel | x <- increments] | y <- increments] where increments = [0.0, incrementSize .. ] window :: (Int, Int) -> (Int, Int) -> [[a]] -> [[a]] window (x0, y0) (x1, y1) = range x0 x1 . map (range y0 y1) where range m n = take (n - m) . drop m

To answer the question in your subject, yes! We have a complex type. Not only does that make the code simpler and more obvious and idiomatic, but it's also more efficient because for this use you'd really prefer a strict pair type for "Point", and complex is strict in it's components. On Sun, 2008-07-06 at 21:02 -0400, Michael Feathers wrote:
Decided a while ago to write some code to calculate the Mandelbrot set using the escape iterations algorithm. Discovered after mulling it about that I could just built it as an infinite list of infinite lists and then extract any rectangle of values that I wanted:
type Point = (Double, Double)
sq :: Double -> Double sq x = x ^ 2
translate :: Point -> Point -> Point translate (r0, i0) (r1, i1) = (r0 + r1, i0 + i1)
mandel :: Point -> Point mandel (r, i) = (sq r + sq i, 2 * r * i)
notEscaped :: Point -> Bool notEscaped (r, i) = (sq r + sq i) <= 4.0
trajectory :: (Point -> Point) -> [Point] trajectory pointFunction = takeWhile notEscaped $ iterate pointFunction seed where seed = (0.0, 0.0)
escapeIterations :: (Point -> Point) -> Int escapeIterations = length . tail . take 1024 . trajectory
mandelbrot :: Double -> [[Int]] mandelbrot incrementSize = [[ escapeIterations $ translate (x, y) . mandel | x <- increments] | y <- increments] where increments = [0.0, incrementSize .. ]
window :: (Int, Int) -> (Int, Int) -> [[a]] -> [[a]] window (x0, y0) (x1, y1) = range x0 x1 . map (range y0 y1) where range m n = take (n - m) . drop m
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks. Here's a newb question: what does strictness really get me in this code? BTW, I only noticed the Complex type late. I looked at it and noticed that all I'd be using is the constructor and add. Didn't seem worth the change. Michael Derek Elkins wrote:
To answer the question in your subject, yes! We have a complex type. Not only does that make the code simpler and more obvious and idiomatic, but it's also more efficient because for this use you'd really prefer a strict pair type for "Point", and complex is strict in it's components.
On Sun, 2008-07-06 at 21:02 -0400, Michael Feathers wrote:
Decided a while ago to write some code to calculate the Mandelbrot set using the escape iterations algorithm. Discovered after mulling it about that I could just built it as an infinite list of infinite lists and then extract any rectangle of values that I wanted:
type Point = (Double, Double)
sq :: Double -> Double sq x = x ^ 2
translate :: Point -> Point -> Point translate (r0, i0) (r1, i1) = (r0 + r1, i0 + i1)
mandel :: Point -> Point mandel (r, i) = (sq r + sq i, 2 * r * i)
notEscaped :: Point -> Bool notEscaped (r, i) = (sq r + sq i) <= 4.0
trajectory :: (Point -> Point) -> [Point] trajectory pointFunction = takeWhile notEscaped $ iterate pointFunction seed where seed = (0.0, 0.0)
escapeIterations :: (Point -> Point) -> Int escapeIterations = length . tail . take 1024 . trajectory
mandelbrot :: Double -> [[Int]] mandelbrot incrementSize = [[ escapeIterations $ translate (x, y) . mandel | x <- increments] | y <- increments] where increments = [0.0, incrementSize .. ]
window :: (Int, Int) -> (Int, Int) -> [[a]] -> [[a]] window (x0, y0) (x1, y1) = range x0 x1 . map (range y0 y1) where range m n = take (n - m) . drop m
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Now Playing: Clammbon - 246 http://youtube.com/watch?v=PO77bN8W1mA

On Mon, Jul 7, 2008 at 2:21 PM, Michael Feathers
Thanks. Here's a newb question: what does strictness really get me in this code?
A bit of speed and memory improvements, I suspect. The type (Double,Double) has three boxes, one for the tuple and one for each double. The type Complex, which is defined as data Complex a = !a :+ !a has one box (after -funbox-strict-fields has done its work), the one for the type as a whole. So it will end up using less memory, and there will be fewer jumps to evaluate one (a jump is made for each box).
BTW, I only noticed the Complex type late. I looked at it and noticed that all I'd be using is the constructor and add. Didn't seem worth the change.
You would also be using the multiply and magnitude functions! And you would gain code readability, since you could define: mandel c z = z^2 + c trajectory c = iterate (mandel c) 0 Which is basically the mathematical definition right there in front of you, instead of splayed out all over the place. Luke

On 2008-07-07, Luke Palmer
On Mon, Jul 7, 2008 at 2:21 PM, Michael Feathers
wrote: BTW, I only noticed the Complex type late. I looked at it and noticed that all I'd be using is the constructor and add. Didn't seem worth the change.
You would also be using the multiply and magnitude functions!
Well, he should continue to use a custom "magnitude squared" function, to save the square-rooting. -- Aaron Denney -><-

lrpalmer:
On Mon, Jul 7, 2008 at 2:21 PM, Michael Feathers
wrote: Thanks. Here's a newb question: what does strictness really get me in this code?
A bit of speed and memory improvements, I suspect. The type (Double,Double) has three boxes, one for the tuple and one for each double. The type Complex, which is defined as
data Complex a = !a :+ !a
has one box (after -funbox-strict-fields has done its work), the one for the type as a whole. So it will end up using less memory, and there will be fewer jumps to evaluate one (a jump is made for each box).
On a good day the two Double components will be unpacked into registers entirely. As here, a loop on Complex: {-# OPTIONS -funbox-strict-fields #-} module M where data Complex = !Double :+ !Double conjugate :: Complex -> Complex conjugate (x:+y) = x :+ (-y) realPart :: Complex -> Double realPart (x :+ _) = x go :: Complex -> Double go n | realPart n > pi = realPart n | otherwise = go (conjugate n) Note that notionally Complex has 3 indirections, the Complex constructor, and two for the Doubles. After optimisation however, there's only unboxed doubles in registers left: M.$wgo :: Double# -> Double# -> Double# M.$wgo = \ (ww_sjT :: Double#) (ww1_sjU :: Double#) -> case >## ww_sjT 3.141592653589793 of wild_Xs { False -> M.$wgo ww_sjT (negateDouble# ww1_sjU); True -> ww_sjT -- Don

Don Stewart
splitAt n xs = (take n xs, drop n xs)
Thanks. That is odd, though. It makes me wonder what to expect re optimization. Would the compiler/runtime know that splitAt could be done in a single pass?
Not with that definition. It would require some moderately unusual fusion combining the take and drop into a single fold with the (,) on the inside, rather than on the outside.
Uhm, but I'm quite sure I saw a paper about how the garbage collector could discover this, and update both thunks simultaneously. (Unfortunately, I can't seem to find it now.) -k -- If I haven't seen further, it is by standing in the footprints of giants
participants (6)
-
Aaron Denney
-
Derek Elkins
-
Don Stewart
-
Ketil Malde
-
Luke Palmer
-
Michael Feathers