
#16004: Vector performance regression in GHC 8.6 -------------------------------------+------------------------------------- Reporter: guibou | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.3 Component: Compiler | Version: 8.6.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hello. With the following code, I can observe a performance regression between ghc 8.4 and 8.6: {{{#!haskell {-# LANGUAGE ScopedTypeVariables #-} module Main where import qualified Data.Vector.Unboxed.Mutable as Vector import qualified Data.Vector.Unboxed as VectorU import Data.Foldable (for_) main :: IO () main = do let n = 1000 let vUnmutable :: VectorU.Vector Double = VectorU.generate (n * n) (\i -> fromIntegral i) v :: Vector.IOVector Double <- VectorU.unsafeThaw vUnmutable for_ [0..(n - 1)] $ \k -> do for_ [0..(n - 1)] $ \i -> do for_ [0..(n - 1)] $ \j -> do a <- Vector.unsafeRead v (i * n + k) b <- Vector.unsafeRead v (k * n + j) c <- Vector.unsafeRead v (i * n + j) Vector.unsafeWrite v (i * n + j) (min (a + b) c) }}} Built with `-O2` and with / without `-fllvm`. I'm using `vector-0.12.0.1`. Here are the timing results: GHC 8.2.2 no llvm: 1.7s llvm: 1.0s GHC 8.4.4 no llvm: 1.6s llvm: 0.9s GHC 8.6.2 no llvm: 4.8s llvm: 4.3s I'm using the following bash + nix script to gather theses timings: {{{#!bash nix-shell -p 'haskell.packages.ghc822.ghcWithPackages(p: [p.vector])' --run "ghc-pkg list | grep vector; ghc -O2 FloydBench.hs -Wall -fforce- recomp; time ./FloydBench" nix-shell -p 'haskell.packages.ghc822.ghcWithPackages(p: [p.vector])' -p llvm_39 --run "ghc-pkg list | grep vector; ghc -O2 FloydBench.hs -Wall -fforce-recomp -fllvm; time ./FloydBench" nix-shell -p 'haskell.packages.ghc844.ghcWithPackages(p: [p.vector])' --run "ghc-pkg list | grep vector; ghc -O2 FloydBench.hs -Wall -fforce- recomp; time ./FloydBench" nix-shell -p 'haskell.packages.ghc844.ghcWithPackages(p: [p.vector])' -p llvm_5 --run "ghc-pkg list | grep vector; ghc -O2 FloydBench.hs -Wall -fforce-recomp -fllvm; time ./FloydBench" nix-shell -p 'haskell.packages.ghc862.ghcWithPackages(p: [p.vector])' --run "ghc-pkg list | grep vector; ghc -O2 FloydBench.hs -Wall -fforce- recomp; time ./FloydBench" nix-shell -p 'haskell.packages.ghc862.ghcWithPackages(p: [p.vector])' -p llvm_6 --run "ghc-pkg list | grep vector; ghc -O2 FloydBench.hs -Wall -fforce-recomp -fllvm; time ./FloydBench" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16004 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler