
Hello, I got great performance difference for the following code if I used type `Int` rather than `Data.Word.Word32`. Anyone can help to explain why such difference? Thanks a lot. -Simon module Main where import Data.Word main :: IO () main = print $ p14 p14 = maximum [ (startChain n 0, n) | n <- [2..1000000] ] startChain :: Word32 -> Int -> Int startChain 1 count = count + 1 startChain n count = startChain (intTransform n) (count+1) intTransform :: Word32 -> Word32 intTransform n | even n = n `div` 2 | otherwise = 3 * n + 1

On Saturday 19 November 2011, 09:09:50, Haisheng Wu wrote:
Hello, I got great performance difference for the following code if I used type `Int` rather than `Data.Word.Word32`. Anyone can help to explain why such difference?
Short answer: GHC optimises Int calculations far better than Word32 calculations, rather, it optimises more calculations for Int than for Word32. It also optimises more calculations for Word than for Word32, but not as many as for Int. The reason is that Int (and Word) are (at least expected to be) far more often used, so the effort has gone to these types primarily. Work is being done to get the fixed-width types on par, but it's not around the corner yet. You can try using Word instead of Word32, that's likely to be faster. But
Thanks a lot.
-Simon
module Main where import Data.Word
main :: IO () main = print $ p14
p14 = maximum [ (startChain n 0, n) | n <- [2..1000000] ]
You get overflow using 32-bit types here.
startChain :: Word32 -> Int -> Int startChain 1 count = count + 1 startChain n count = startChain (intTransform n) (count+1)
intTransform :: Word32 -> Word32 intTransform n
| even n = n `div` 2 | otherwise = 3 * n + 1

Hmm... I think I made a little confusion so I put my finding here: http://haisgwu.info/posts/2011-11-20-euler-problem-14.html I do got stack overflow thus need several compile opts to fix it. Not sure if it is what you mean by "You get overflow using 32-bit types here." -Haisheng On Sat, Nov 19, 2011 at 10:49 PM, Daniel Fischer < daniel.is.fischer@googlemail.com> wrote:
On Saturday 19 November 2011, 09:09:50, Haisheng Wu wrote:
Hello, I got great performance difference for the following code if I used type `Int` rather than `Data.Word.Word32`. Anyone can help to explain why such difference?
Short answer: GHC optimises Int calculations far better than Word32 calculations, rather, it optimises more calculations for Int than for Word32. It also optimises more calculations for Word than for Word32, but not as many as for Int.
The reason is that Int (and Word) are (at least expected to be) far more often used, so the effort has gone to these types primarily. Work is being done to get the fixed-width types on par, but it's not around the corner yet.
You can try using Word instead of Word32, that's likely to be faster.
But
Thanks a lot.
-Simon
module Main where import Data.Word
main :: IO () main = print $ p14
p14 = maximum [ (startChain n 0, n) | n <- [2..1000000] ]
You get overflow using 32-bit types here.
startChain :: Word32 -> Int -> Int startChain 1 count = count + 1 startChain n count = startChain (intTransform n) (count+1)
intTransform :: Word32 -> Word32 intTransform n
| even n = n `div` 2 | otherwise = 3 * n + 1

On 20.11.2011 07:50, Haisheng Wu wrote:
Hmm... I think I made a little confusion so I put my finding here: http://haisgwu.info/posts/2011-11-20-euler-problem-14.html
I do got stack overflow thus need several compile opts to fix it. Not sure if it is what you mean by "You get overflow using 32-bit types here."
No, what he meant was that your n does not always fit into a 32-bit integer, so the integer will overflow (i.e. once it exceeds its maximum value it will wrap around and become negative).

On Sunday 20 November 2011, 13:53:20, Sebastian Hungerecker wrote:
On 20.11.2011 07:50, Haisheng Wu wrote:
Hmm... I think I made a little confusion so I put my finding here: http://haisgwu.info/posts/2011-11-20-euler-problem-14.html
I do got stack overflow thus need several compile opts to fix it. Not sure if it is what you mean by "You get overflow using 32-bit types here."
No, what he meant was that your n does not always fit into a 32-bit integer, so the integer will overflow (i.e. once it exceeds its maximum value it will wrap around and become negative).
That. With Word32 you won't get negative values of course, but the wrapped-around values are completely bogus nevertheless. With signed 32-bit integers, the overflow puts you into an infinite loop of negative values for several starting values, the smallest is something around 113000 iirc. With Word32, I never tested what the smallest starting value landing you in an infinite loop is, but (2^32-1)/3 surely does (~> 0 ~> 0).
participants (3)
-
Daniel Fischer
-
Haisheng Wu
-
Sebastian Hungerecker