[commit: packages/containers] ghc-head: highestBitMap: clean-room reimplementation (8a1e9be)
git at git.haskell.org
git at git.haskell.org
Fri Aug 30 13:34:43 CEST 2013
Repository : ssh://git@git.haskell.org/containers
On branch : ghc-head
Link : http://git.haskell.org/?p=packages/containers.git;a=commit;h=8a1e9be082d525f9373800921d3876809ea527d4
>---------------------------------------------------------------
commit 8a1e9be082d525f9373800921d3876809ea527d4
Author: Johan Tibell <johan.tibell at gmail.com>
Date: Wed Dec 12 16:55:55 2012 -0800
highestBitMap: clean-room reimplementation
Replaced the previous implementation due to licensing concerns. The new
implementation is a clean-room reimplementation by Clark Gaebel, based
on the public domain implementation at
http://graphics.stanford.edu/~seander/bithacks.html#RoundUpPowerOf2
>---------------------------------------------------------------
8a1e9be082d525f9373800921d3876809ea527d4
Data/IntMap/Base.hs | 64 +++++++++++----------------------------------------
1 file changed, 14 insertions(+), 50 deletions(-)
diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index d15d7c6..fccda5a 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -2067,59 +2067,23 @@ branchMask p1 p2
= intFromNat (highestBitMask (natFromInt p1 `xor` natFromInt p2))
{-# INLINE branchMask #-}
-{----------------------------------------------------------------------
- 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
-
- highestBit: method cycles
- --------------
- frexp 195
- float 33
- bit 11
- asm 11
-
- 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.
-----------------------------------------------------------------------}
+-- 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 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
+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 !(defined(__GLASGOW_HASKELL__) && WORD_SIZE_IN_BITS==32)
- x5 -> case (x5 .|. shiftRL x5 32) of -- for 64 bit platforms
+ x7 = x6 .|. x6 `shiftR` 32
+ in x7 `xor` (x7 `shiftR` 1)
+#else
+ in x6 `xor` (x6 `shiftR` 1)
#endif
- x6 -> (x6 `xor` (shiftRL x6 1))
{-# INLINE highestBitMask #-}
More information about the ghc-commits
mailing list