#1246: <= operators get compiled worse than ==
----------------------+-----------------------------------------------------
Reporter: duncan | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 6.6.2
Component: Compiler | Version: 6.6
Severity: normal | Resolution:
Keywords: | Difficulty: Unknown
Testcase: | Architecture: x86
Os: Unknown |
----------------------+-----------------------------------------------------
Changes (by simonmar):
* milestone: => 6.6.2
Comment:
The only difference I see between the assembly generated by these two
examples (with -fasm, at least) is that the sense of the branch is
different; in the first case the branch is forward and usually not-taken,
and in the second case the branch is forward and taken. There's also one
superfluous reg-to-reg move in the second (supposedly faster) case.
I tried to reproduce the result, but failed. In my test (on an Opteron),
the first version was always quicker with both -fasm and -fvia-C. Test
code below:
{{{
{-# OPTIONS_GHC -cpp #-}
module Main where
import Prelude hiding (take)
import System.CPUTime
#if 0
take :: Int -> [a] -> [a]
take n _ | n <= 0 = []
take _ [] = []
take n (x:xs) = x : take (n-1) xs
#else
take :: Int -> [a] -> [a]
take n _ | n <= 0 = []
take n ls = take' n ls
where
take' :: Int -> [a] -> [a]
take' 0 _ = []
take' _ [] = []
take' n (x:xs) = x : take' (n-1) xs
#endif
main = do
let list = [1..10000000]
l = length list
l `seq` return ()
t1 <- getCPUTime
length (take l list) `seq` return ()
t2 <- getCPUTime
print ((t2 - t1) `quot` 1000000)
}}}
If this turns out to be a branch prediction issue, we can close it as a
dup of #849.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1246>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs