[vector] #20: Optimization strategy unclear (-Odph / -O2)
vector
vector at projects.haskell.org
Sun May 16 18:27:26 EDT 2010
#20: Optimization strategy unclear (-Odph / -O2)
--------------------+-------------------------------------------------------
Reporter: choener | Owner:
Type: defect | Status: new
Priority: minor | Milestone: 0.7
Version: 0.6 | Keywords: documentation, optimization
--------------------+-------------------------------------------------------
The vector tutorial states that -Odph should be used. On ghc 6.12.1 this
leads to abysmal performance with some functions. Simple program attached.
n=20000 has 60s (dph) vs. 5s (O2).
"g n" is for comparison only and requires 12s (O2) if you are interested.
-fno-method-sharing is required for good vector performance (otherwise:
17s).
{{{
{-# OPTIONS_GHC -fno-method-sharing #-}
module Main where
import qualified Data.Vector.Unboxed as V
import System.Environment (getArgs)
f :: Int -> Int
f n = V.sum $ V.concatMap (\k -> V.enumFromN 1 k) $ V.enumFromN 1 n
g :: Int -> Int
g n = sum $ concatMap (\k -> enumFromTo 1 k) $ enumFromTo 1 n
main = do
(a:_) <- getArgs
let n = read a :: Int
print $ f n
}}}
--
Ticket URL: <http://trac.haskell.org/vector/ticket/20>
vector <http://trac.haskell.org/vector>
Package vector
More information about the vector
mailing list