Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/26b449ee3fbf02bc0cea109f967ef08070a4a97e

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

commit 26b449ee3fbf02bc0cea109f967ef08070a4a97e
Author: Johan Tibell <[email protected]>
Date:   Wed Dec 12 18:07:08 2012 -0800

    GHC.Event.IntMap.highestBitMap reimplementation
    
    Replaced the previous implementation due to licensing concerns. The new
    implementation is a reimplementation by Clark Gaebel, based on the
    public domain implementation at
    http://graphics.stanford.edu/~seander/bithacks.html#RoundUpPowerOf2

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

 GHC/Event/IntMap.hs |   63 +++++++++++++-------------------------------------
 1 files changed, 17 insertions(+), 46 deletions(-)

diff --git a/GHC/Event/IntMap.hs b/GHC/Event/IntMap.hs
index 6c397e5..7e7814e 100644
--- a/GHC/Event/IntMap.hs
+++ b/GHC/Event/IntMap.hs
@@ -327,50 +327,21 @@ branchMask :: Prefix -> Prefix -> Mask
 branchMask p1 p2
     = intFromNat (highestBitMask (natFromInt p1 `xor` natFromInt p2))
 
-{-
-Finding the highest bit mask in a word [x] can be done efficiently in
-three ways:
-
-* convert to a floating point value and the mantissa tells us the
-  [log2(x)] that corresponds with the highest bit position. The mantissa
-  is retrieved either via the standard C function [frexp] or by some bit
-  twiddling on IEEE compatible numbers (float). Note that one needs to
-  use at least [double] precision for an accurate mantissa of 32 bit
-  numbers.
-
-* use bit twiddling, a logarithmic sequence of bitwise or's and shifts (bit).
-
-* use processor specific assembler instruction (asm).
-
-The most portable way would be [bit], but is it efficient enough?
-I have measured the cycle counts of the different methods on an AMD
-Athlon-XP 1800 (~ Pentium III 1.8Ghz) using the RDTSC instruction:
-
-highestBitMask: method  cycles
-                --------------
-                 frexp   200
-                 float    33
-                 bit      11
-                 asm      12
-
-Wow, the bit twiddling is on today's RISC like machines even faster
-than a single CISC instruction (BSR)!
--}
-
--- | @highestBitMask@ returns a word where only the highest bit is
--- set.  It is found by first setting all bits in lower positions than
--- the highest bit and than taking an exclusive or with the original
--- value.  Allthough the function may look expensive, GHC compiles
--- this into excellent C code that subsequently compiled into highly
--- efficient machine code. The algorithm is derived from Jorg Arndt's
--- FXT library.
-highestBitMask :: Nat -> Nat
-highestBitMask x0
-  = case (x0 .|. shiftRL x0 1) of
-     x1 -> case (x1 .|. shiftRL x1 2) of
-      x2 -> case (x2 .|. shiftRL x2 4) of
-       x3 -> case (x3 .|. shiftRL x3 8) of
-        x4 -> case (x4 .|. shiftRL x4 16) of
-         x5 -> case (x5 .|. shiftRL x5 32) of   -- for 64 bit platforms
-          x6 -> (x6 `xor` (shiftRL x6 1))
+-- The highestBitMask implementation is based on
+-- http://graphics.stanford.edu/~seander/bithacks.html#RoundUpPowerOf2
+-- which has been put in the public domain.
 
+-- | Return a word where only the highest bit is set.
+highestBitMask :: Nat -> Nat
+highestBitMask x1 = let x2 = x1 .|. x1 `shiftR` 1
+                        x3 = x2 .|. x2 `shiftR` 2
+                        x4 = x3 .|. x3 `shiftR` 4
+                        x5 = x4 .|. x4 `shiftR` 8
+                        x6 = x5 .|. x5 `shiftR` 16
+#if !(WORD_SIZE_IN_BITS==32)
+                        x7 = x6 .|. x6 `shiftR` 32
+                     in x7 `xor` (x7 `shiftR` 1)
+#else
+                     in x6 `xor` (x6 `shiftR` 1)
+#endif
+{-# INLINE highestBitMask #-}



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to