[commit: ghc] ghc-8.4: Add ptr-eq short-cut to `compareByteArrays#` primitive (309d632)

git at git.haskell.org git at git.haskell.org
Mon Jan 29 22:34:21 UTC 2018


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

On branch  : ghc-8.4
Link       : http://ghc.haskell.org/trac/ghc/changeset/309d632c7147b65b9ae017f08d65295e8b1fdbcb/ghc

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

commit 309d632c7147b65b9ae017f08d65295e8b1fdbcb
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Fri Jan 26 13:07:17 2018 -0500

    Add ptr-eq short-cut to `compareByteArrays#` primitive
    
    This is an obvious optimisation whose overhead is neglectable but
    which significantly simplifies the common uses of `compareByteArrays#`
    which would otherwise require to make *careful* use of
    `reallyUnsafePtrEquality#` or (equally fragile) `byteArrayContents#`
    which can result in less optimal assembler code being generated.
    
    Test Plan: carefully examined generated cmm/asm code; validate via phab
    
    Reviewers: alexbiehl, bgamari, simonmar
    
    Reviewed By: bgamari, simonmar
    
    Subscribers: rwbarton, thomie, carter
    
    Differential Revision: https://phabricator.haskell.org/D4319
    
    (cherry picked from commit 31c260f3967d2c06063c962a98475058daa45c6d)


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

309d632c7147b65b9ae017f08d65295e8b1fdbcb
 compiler/codeGen/StgCmmPrim.hs | 43 ++++++++++++++++++++++++++++++++++++++++++
 1 file changed, 43 insertions(+)

diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs
index cd61e36..ff0eebd 100644
--- a/compiler/codeGen/StgCmmPrim.hs
+++ b/compiler/codeGen/StgCmmPrim.hs
@@ -1746,8 +1746,51 @@ doCompareByteArraysOp res ba1 ba1_off ba2 ba2_off n = do
     dflags <- getDynFlags
     ba1_p <- assignTempE $ cmmOffsetExpr dflags (cmmOffsetB dflags ba1 (arrWordsHdrSize dflags)) ba1_off
     ba2_p <- assignTempE $ cmmOffsetExpr dflags (cmmOffsetB dflags ba2 (arrWordsHdrSize dflags)) ba2_off
+
+    -- short-cut in case of equal pointers avoiding a costly
+    -- subroutine call to the memcmp(3) routine; the Cmm logic below
+    -- results in assembly code being generated for
+    --
+    --   cmpPrefix10 :: ByteArray# -> ByteArray# -> Int#
+    --   cmpPrefix10 ba1 ba2 = compareByteArrays# ba1 0# ba2 0# 10#
+    --
+    -- that looks like
+    --
+    --          leaq 16(%r14),%rax
+    --          leaq 16(%rsi),%rbx
+    --          xorl %ecx,%ecx
+    --          cmpq %rbx,%rax
+    --          je l_ptr_eq
+    --
+    --          ; NB: the common case (unequal pointers) falls-through
+    --          ; the conditional jump, and therefore matches the
+    --          ; usual static branch prediction convention of modern cpus
+    --
+    --          subq $8,%rsp
+    --          movq %rbx,%rsi
+    --          movq %rax,%rdi
+    --          movl $10,%edx
+    --          xorl %eax,%eax
+    --          call memcmp
+    --          addq $8,%rsp
+    --          movslq %eax,%rax
+    --          movq %rax,%rcx
+    --  l_ptr_eq:
+    --          movq %rcx,%rbx
+    --          jmp *(%rbp)
+
+    l_ptr_eq <- newBlockId
+    l_ptr_ne <- newBlockId
+
+    emit (mkAssign (CmmLocal res) (zeroExpr dflags))
+    emit (mkCbranch (cmmEqWord dflags ba1_p ba2_p)
+                    l_ptr_eq l_ptr_ne (Just False))
+
+    emitLabel l_ptr_ne
     emitMemcmpCall res ba1_p ba2_p n 1
 
+    emitLabel l_ptr_eq
+
 -- ----------------------------------------------------------------------------
 -- Copying byte arrays
 



More information about the ghc-commits mailing list