[GHC] #7367: Optimiser / Linker Problem on amd64
GHC
ghc-devs at haskell.org
Wed Aug 28 16:56:40 UTC 2013
#7367: Optimiser / Linker Problem on amd64
--------------------------------------------+------------------------------
Reporter: wurmli | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.8.1
Component: Build System | Version: 7.6.1
Resolution: | Keywords:
Operating System: Linux | Architecture: x86_64
Type of failure: Runtime performance bug | (amd64)
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by wurmli):
May I add to your consideration the following simple example whith the
same structure and behaviour:
{{{
-- ghc --make -threaded -O2 -fllvm -rtsopts heapAndSpeed.hs
-- ./headAndSpeed +RTS -s
{-# LANGUAGE BangPatterns #-}
import System.Environment
import Control.Applicative
import Control.Monad
import Control.Monad.ST
import qualified Data.STRef as VSM
-------------------------------------------------------------------
-- Increment counter by 1
acc1 :: VSM.STRef s ( Int , Int ) -> ST s ()
acc1 !v = do{
(!k,!n) <- VSM.readSTRef v;
VSM.writeSTRef v (k+1,n)
}
-- Increment counter until limit
whileModify1 :: VSM.STRef s ( Int , Int ) -> ST s ()
whileModify1 !v = do
!go <- do{ (k,n) <- VSM.readSTRef v; return (compare k n)}
case go of
LT -> do {acc1 v; whileModify1 v}
EQ -> return ()
GT -> return ()
testAcc :: Int -> (Int,Int)
testAcc n = runST $ do
v <- VSM.newSTRef (0,n)
whileModify1 v
VSM.readSTRef v
main = do
let k = 20000000
putStrLn $ show $ testAcc k
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/7367#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list