[commit: ghc] master: Minor performance optimisation (8707911)

git at git.haskell.org git at git.haskell.org
Thu Nov 22 09:57:24 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/8707911a8ba42619e77315f7c0443546991a6668/ghc

>---------------------------------------------------------------

commit 8707911a8ba42619e77315f7c0443546991a6668
Author: Gabor Greif <ggreif at gmail.com>
Date:   Wed Nov 21 18:30:49 2018 +0100

    Minor performance optimisation
    
    only concat once


>---------------------------------------------------------------

8707911a8ba42619e77315f7c0443546991a6668
 compiler/llvmGen/LlvmCodeGen.hs | 10 +++++-----
 1 file changed, 5 insertions(+), 5 deletions(-)

diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs
index 3fcf83a..b003cbc 100644
--- a/compiler/llvmGen/LlvmCodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, TypeFamilies #-}
+{-# LANGUAGE CPP, TypeFamilies, ViewPatterns #-}
 
 -- -----------------------------------------------------------------------------
 -- | This is the top-level module in the LLVM code generator.
@@ -125,13 +125,13 @@ cmmDataLlvmGens :: [(Section,CmmStatics)] -> LlvmM ()
 cmmDataLlvmGens statics
   = do lmdatas <- mapM genLlvmData statics
 
-       let (gss, tss) = unzip lmdatas
+       let (concat -> gs, tss) = unzip lmdatas
 
        let regGlobal (LMGlobal (LMGlobalVar l ty _ _ _ _) _)
                         = funInsert l ty
-           regGlobal _  = return ()
-       mapM_ regGlobal (concat gss)
-       gss' <- mapM aliasify $ concat gss
+           regGlobal _  = pure ()
+       mapM_ regGlobal gs
+       gss' <- mapM aliasify $ gs
 
        renderLlvm $ pprLlvmData (concat gss', concat tss)
 



More information about the ghc-commits mailing list