Solving a geometry problem with Haskell

Hello, I have been browsing through the problems at projecteuler.net and I found one that seemed interesting. It's the problem 176, I'll state it here: The four rectangular triangles with sides (9,12,15), (12,16,20), (5,12,13) and (12,35,37) all have one of the shorter sides (catheti) equal to 12. It can be shown that no other integer sided rectangular triangle exists with one of the catheti equal to 12. Find the smallest integer that can be the length of a cathetus of exactly 47547 different integer sided rectangular triangles. I thought I've solved it nicely, only to find later on that my solution was too slow (it has been running for almost three days now). While I was creating my solution I used literate haskell, which I think helped me a bunch to think about the problem. I wrote it originally in portuguese -- the portuguese literate version has all the attempts I've made until getting to the final one. For posting it here I've translated the reasoning around the attempt that solved the problem -- although it does it very slow -- into a new .lhs file: http://www.dcc.ufmg.br/~rafaelc/problem176.lhs After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function. So I began researching about better ways to write that functio. Someone pointed to me on #haskell that the C library gmp has such a function. So I went ahead and wrote a C version of the program using gmp: http://www.dcc.ufmg.br/~rafaelc/problem176.c It's not the prettiest C code, as I did it really quickly, simply translating haskell code into C, but I believe it works. That C solution has been running for more than one hour now and no solution has come up yet. So I don't think it's worthed even writing a faster isPerfectSquare in haskell. As I was translating from Portuguese to English I revisited my logic and I can't see any problems with it. I think the problem is only of slowness, really. Does anyone have a better idea for how I should try to solve this problem? I'm all out of ideas. []'s Rafael

On Jan 12, 2008 10:19 PM, Rafael Almeida
After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function.
I guess that Haskell's referential transparence means the answers to the isPerfectSquare will be cached, ie automatically memoized? (not sure if is correct term?) Just out of interest, what is the upper bound for the catheti in the question? How much memory is the perfectSquares list taking up? One thought: - you're calculating the square by multiplying two numbers, maybe that could be done more quickly Quick back of envelope: 1 x 1 = 1 2 x 2 = 4 = 1 + 1 + 2 3 x 3 = 9 = 4 + 2 + 3 4 x 4 = 16 = 9 + 3 + 4 ... in other words, you can use dynamic programming to calculate each perfect square, getting each square as: square(n+1) = square(n) + (n - 1) + (n) Maybe this could save some CPU?

On Sat, 12 Jan 2008, Hugh Perkins wrote:
On Jan 12, 2008 10:19 PM, Rafael Almeida
wrote: After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function.
I guess that Haskell's referential transparence means the answers to the isPerfectSquare will be cached, ie automatically memoized? (not sure if is correct term?)

On 12/01/2008, Hugh Perkins
On Jan 12, 2008 10:19 PM, Rafael Almeida
wrote: After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function.
I guess that Haskell's referential transparence means the answers to the isPerfectSquare will be cached, ie automatically memoized? (not sure if is correct term?)
This isn't true unless calling isPerfectSquare reads the result out of a lazily generated array of responses or some other data structure at the top-level. There's no memoisation of functions by default because it would typically require ridiculous amounts of memory, however, you can usually rely on values bound to variables to only be computed once, barring those which are typeclass polymorphic. - Cale

On Jan 12, 2008 9:19 PM, Rafael Almeida
After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function.
That function is quite inefficient for large numbers. You might try something like this: isPerfectSquare n = searchSquare 0 n where searchSquare lo hi | lo == hi = False | otherwise = let mid = (lo + hi) `div` 2 in case mid^2 `compare` n of EQ -> True LT -> searchSquare mid hi GT -> searchSquare lo mid Luke

You can do better than this, too, actually. It looks like you're
using isPerfectSquare inside a filter, which is given a monotone
sequence. That means we can do:
-- finds the intersection of two monotone sequences
intersectMonotone :: (Ord a) => [a] -> [a] -> [a]
intersectMonotone (x:xs) (y:ys) =
case x `compare` y of
EQ -> x : intersectMonotone x y
LT -> intersectMonotone xs (y:ys)
GT -> intersectMonotone (x:xs) ys
intersectMonotone _ _ = []
Then you can change (filter isPerfectSquare) to (intersectMonotone
perfectSquares) and you should get a big speed boost.
Luke
On Jan 12, 2008 9:48 PM, Luke Palmer
On Jan 12, 2008 9:19 PM, Rafael Almeida
wrote: After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function.
That function is quite inefficient for large numbers. You might try something like this:
isPerfectSquare n = searchSquare 0 n where searchSquare lo hi | lo == hi = False | otherwise = let mid = (lo + hi) `div` 2 in case mid^2 `compare` n of EQ -> True LT -> searchSquare mid hi GT -> searchSquare lo mid
Luke

Am Samstag, 12. Januar 2008 22:48 schrieb Luke Palmer:
On Jan 12, 2008 9:19 PM, Rafael Almeida
wrote: After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function.
That function is quite inefficient for large numbers. You might try something like this:
isPerfectSquare n = searchSquare 0 n where searchSquare lo hi
| lo == hi = False | otherwise =
let mid = (lo + hi) `div` 2 in case mid^2 `compare` n of EQ -> True LT -> searchSquare mid hi GT -> searchSquare lo mid
Luke
I don't want to be a spoil-sport, but that won't help much either. And although the logic of the programme is correct, the numbers involved are so large that I'd expect the running time to be rather years than days (it took a minute to solve for the smallest cathetus of 6 triangles, 128). Suppose the answer were 10^9 (it's much larger, actually). Then the limit for the other cathetus would be roughly 5*10^17 and for all these values it has to be checked whether n^2 + y^2 is a perfect square. If one check took a nanosecond, that would be roughly 5*10^8 seconds or nearly 16 years. Rafael, you have some good starts, but to get the answer in a reasonable time, you must employ some more algebra. Find a way to determine a cathetus of how many triangles a number is without actually constructing them is a good step. Cheers, Daniel

On Sat, 12 Jan 2008 23:36:43 +0100, Daniel Fischer
Am Samstag, 12. Januar 2008 22:48 schrieb Luke Palmer:
On Jan 12, 2008 9:19 PM, Rafael Almeida
wrote: After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function.
That function is quite inefficient for large numbers. You might try something like this:
isPerfectSquare n > where searchSquare lo hi
| lo = hi > | otherwise > let mid > case mid^2 `compare` n of EQ -> True LT -> searchSquare mid hi GT -> searchSquare lo mid
Luke
I don't want to be a spoil-sport, but that won't help much either. And although the logic of the programme is correct, the numbers involved are so large that I'd expect the running time to be rather years than days (it took a minute to solve for the smallest cathetus of 6 triangles, 128). Suppose the answer were 10^9 (it's much larger, actually). Then the limit for the other cathetus would be roughly 5*10^17 and for all these values it has to be checked whether n^2 + y^2 is a perfect square. If one check took a nanosecond, that would be roughly 5*10^8 seconds or nearly 16 years. Rafael, you have some good starts, but to get the answer in a reasonable time, you must employ some more algebra. Find a way to determine a cathetus of how many triangles a number is without actually constructing them is a good step.
Cheers, Daniel
Now you really conviced me that the algorithm isn't right. Although I already thought I needed to come up with a new algorithm when the GMP's perfect square function didn't help. I thank for all the feedback on how to make isPerfectSquare faster, though. It has been educational. I'm trying to come up with something other than constructing the triangles, but maybe I'm just not that strong at algebra. Thanks for de feedback, though.

"Rafael Almeida"
perfectSquares :: [Integer] perfectSquares = zipWith (*) [1..] [1..]
isPerfectSquare :: Integer -> Bool isPerfectSquare x = (head $ dropWhile (
what about module Main where isPerfectSquare :: Integer -> Bool isPerfectSquare n = sqrrt == fromIntegral (truncate sqrrt) where sqrrt = sqrt $ fromIntegral n ? It's a hell alot faster, but I have no idea if some numerical property of square roots could make it give different results than your version, in rare cases. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

On Sat, 12 Jan 2008, Achim Schneider wrote:
"Rafael Almeida"
wrote: perfectSquares :: [Integer] perfectSquares = zipWith (*) [1..] [1..]
isPerfectSquare :: Integer -> Bool isPerfectSquare x = (head $ dropWhile (
what about
module Main where
isPerfectSquare :: Integer -> Bool isPerfectSquare n = sqrrt == fromIntegral (truncate sqrrt) where sqrrt = sqrt $ fromIntegral n
? It's a hell alot faster, but I have no idea if some numerical property of square roots could make it give different results than your version, in rare cases.
The rare cases occur for big numbers. http://www.haskell.org/haskellwiki/Generic_number_type#isSquare

G'day all.
Quoting Henning Thielemann
The rare cases occur for big numbers. http://www.haskell.org/haskellwiki/Generic_number_type#isSquare
How big, you might ask? Prelude> let dd = undefined :: Double in floatRadix dd ^ floatDigits dd 9007199254740992 Pretty big, and covering enough cases that it's worth the optimisation when it applies: http://andrew.bromage.org/darcs/numbertheory/Math/Util.hs Cheers, Andrew Bromage

Achim Schneider
"Rafael Almeida"
wrote: perfectSquares :: [Integer] perfectSquares = zipWith (*) [1..] [1..]
isPerfectSquare :: Integer -> Bool isPerfectSquare x = (head $ dropWhile (
what about
module Main where
isPerfectSquare :: Integer -> Bool isPerfectSquare n = sqrrt == fromIntegral (truncate sqrrt) where sqrrt = sqrt $ fromIntegral n
? It's a hell alot faster, but I have no idea if some numerical property of square roots could make it give different results than your version, in rare cases.
Well, even if so, I bet calculating the square root by successive approximation using integers would still be faster, it's O(ld(n)) instead of O(n). -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Achim Schneider
Achim Schneider
wrote: "Rafael Almeida"
wrote: perfectSquares :: [Integer] perfectSquares = zipWith (*) [1..] [1..]
isPerfectSquare :: Integer -> Bool isPerfectSquare x = (head $ dropWhile (
what about
module Main where
isPerfectSquare :: Integer -> Bool isPerfectSquare n = sqrrt == fromIntegral (truncate sqrrt) where sqrrt = sqrt $ fromIntegral n
? It's a hell alot faster, but I have no idea if some numerical property of square roots could make it give different results than your version, in rare cases.
Well, even if so, I bet calculating the square root by successive approximation using integers would still be faster, it's O(ld(n)) instead of O(n).
(and you can use a truncated sqrt as initial guess) This may seem like cheating, but then I'm a game programmer... -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

On Jan 12, 2008 7:12 PM, Achim Schneider
what about
module Main where
isPerfectSquare :: Integer -> Bool isPerfectSquare n = sqrrt == fromIntegral (truncate sqrrt) where sqrrt = sqrt $ fromIntegral n
? It's a hell alot faster, but I have no idea if some numerical property of square roots could make it give different results than your version, in rare cases.
I did something similar:
isSquare :: Integer -> Bool
isSquare x = x == (sqx * sqx)
where sqx = round $ sqrt $ fromInteger x
perfectSquares :: [Integer]
perfectSquares = zipWith (*) [1..] [1..]
findSorted :: [Integer] -> Integer -> Bool
findSorted xs x = h == x
where h : _ = dropWhile (

"Rafael Almeida"
[perfect square problem]
most of this is shamelessly stolen from http://www.haskell.org/haskellwiki/Generic_number_type#squareRoot (^!) :: Num a => a -> Int -> a (^!) x n = x^n isSquare :: Integer -> Bool isSquare n = let newtonStep x = div (x + div n x) 2 iters = iterate newtonStep $ truncate $ sqrt $ fromIntegral n isRoot r = r^!2 <= n && n < (r+1)^!2 root = head $ dropWhile (not . isRoot) iters in root^!2 == n *Main> isSquare (2^1024) True *Main> isSquare (2^1024+1) False *Main> isSquare (2^1024-1) False *Main> isSquare (2^2^16) True the last one take a bit less than 20 secs on my pc. And 2^2^16 is a number that takes at least an hour to pronounce. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Achim Schneider
the last one take a bit less than 20 secs on my pc. And 2^2^16 is a number that takes at least an hour to pronounce.
Which means that I'm an absolute genius when it comes to fucking up perfectly good algorithms. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Hi Rafael, I have just two ideas, that could improve your strategy to reduce the computation time: 1. perhaps there is also a minimum (not only a maximul) for the values you should try 2. is the function howManyTriangles monotone? If yes, then you could try to solve: howManyTriangles n = 47547 by finding an upper n, nmax, where howManyTriangles nmax > 47547, and than using Euler to reduce the interval (from 12 to nmax, then probably from (12 + nmax)/2 to nmax, a.s.o) Then you will have ~ ln nmax computations of the function, which could be better than computing it from 1 to ... Nicu Ionita
-----Ursprüngliche Nachricht----- Von: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] Im Auftrag von Rafael Almeida Gesendet: Samstag, 12. Januar 2008 22:20 An: haskell-cafe@haskell.org Betreff: [Haskell-cafe] Solving a geometry problem with Haskell
Hello,
I have been browsing through the problems at projecteuler.net and I found one that seemed interesting. It's the problem 176, I'll state it here:
The four rectangular triangles with sides (9,12,15), (12,16,20), (5,12,13) and (12,35,37) all have one of the shorter sides (catheti) equal to 12. It can be shown that no other integer sided rectangular triangle exists with one of the catheti equal to 12.
Find the smallest integer that can be the length of a cathetus of exactly 47547 different integer sided rectangular triangles.
I thought I've solved it nicely, only to find later on that my solution was too slow (it has been running for almost three days now). While I was creating my solution I used literate haskell, which I think helped me a bunch to think about the problem. I wrote it originally in portuguese -- the portuguese literate version has all the attempts I've made until getting to the final one. For posting it here I've translated the reasoning around the attempt that solved the problem -- although it does it very slow -- into a new .lhs file:
http://www.dcc.ufmg.br/~rafaelc/problem176.lhs
After some profiling I found out that about 94% of the execution time is spent in the ``isPerfectSquare'' function. So I began researching about better ways to write that functio. Someone pointed to me on #haskell that the C library gmp has such a function. So I went ahead and wrote a C version of the program using gmp:
http://www.dcc.ufmg.br/~rafaelc/problem176.c
It's not the prettiest C code, as I did it really quickly, simply translating haskell code into C, but I believe it works. That C solution has been running for more than one hour now and no solution has come up yet. So I don't think it's worthed even writing a faster isPerfectSquare in haskell.
As I was translating from Portuguese to English I revisited my logic and I can't see any problems with it. I think the problem is only of slowness, really. Does anyone have a better idea for how I should try to solve this problem? I'm all out of ideas.
[]'s Rafael _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, 13 Jan 2008 11:48:09 +0100, "Nicu Ionita"
Hi Rafael,
I have just two ideas, that could improve your strategy to reduce the computation time:
1. perhaps there is also a minimum (not only a maximul) for the values you should try
Yeah, that's a good one, the most I can narrow down the results the better. But if I can figure out the number of triangles without actually constructing them would be the real winner algorithm.
2. is the function howManyTriangles monotone? If yes, then you could try to solve:
howManyTriangles n = 47547
by finding an upper n, nmax, where howManyTriangles nmax > 47547, and than using Euler to reduce the interval (from 12 to nmax, then probably from (12 + nmax)/2 to nmax, a.s.o)
Then you will have ~ ln nmax computations of the function, which could be better than computing it from 1 to ...
I wish it was monotone, but it doesn't seem to be anything, I even plotted the relation cathetus size x number of triangles, but it didn't really show any pattern. It seems there are more likely results, but there are a few of them that looks just random. If you want to see the plotted graph: http://homepages.dcc.ufmg.br/~rafaelc/problem176.png

I haven't solved this problem yet, but I think it has more to do with multiplicative partition than with perfect-square. - Quan
participants (11)
-
Achim Schneider
-
ajb@spamcop.net
-
Andrei Formiga
-
Cale Gibbard
-
Daniel Fischer
-
Henning Thielemann
-
Hugh Perkins
-
Luke Palmer
-
Nicu Ionita
-
Quân Ta
-
Rafael Almeida