[Haskell-cafe] fast integer base-2 log function?

Stefan O'Rear stefanor at cox.net
Tue Feb 26 20:29:02 EST 2008


On Tue, Feb 26, 2008 at 09:33:57PM +0000, Jens Blanck wrote:
> > {-# LANGUAGE MagicHash #-}
> > import GHC.Exts
> > import Data.Bits
> >
> > -- experiment with using a LUT here (hint: FFI + static arrays in C)
> > ilog2i0, ilog2i1, ilog2i2, ilog2i3, ilog2i4 :: Int -> Int -> Int
> > ilog2i0 k x | x .&. 0xFFFF0000 /= 0 = ilog2i1 (k + 16) (x `shiftR` 16)
> >             | otherwise             = ilog2i1 k x
> > ilog2i1 k x | x .&. 0xFF00 /= 0     = ilog2i2 (k + 8)  (x `shiftR` 8)
> >             | otherwise             = ilog2i2 k x
> > ilog2i2 k x | x .&. 0xF0 /= 0       = ilog2i3 (k + 4)  (x `shiftR` 4)
> >             | otherwise             = ilog2i3 k x
> > ilog2i3 k x | x .&. 0xC /= 0        = ilog2i4 (k + 2)  (x `shiftR` 2)
> >             | otherwise             = ilog2i4 k x
> > ilog2i4 k x | x .&. 0x2 /= 0        = k + 1 + (x `shiftR` 1)
> >             | otherwise             = k + x
> >
> > log2i :: Integer -> Int  -- actually returns bit length, and returns
> > garbage on negatives, but do you care?
> > log2i (J# len adr) = ilog2i0 0 (I# (indexIntArray# adr (len -# 1#))) + I#
> > (32# *# (len -# 1#))
> > log2i (S# sml) = ilog2i0 0 (I# sml)
> >
> >
> I tried the above but I got wrong results on 2^31..2^32-1 because in the
> additions in ilog2i4, the number x was -1 because of sign extension
> performed by the shifts all the way (thanks for the ghci debugger). (So,
> yes, I do care somewhat about garbage on negatives :)

This is what you get for only testing on 100 and 2^34, I guess :)

If you change all the Int to Word (unsigned) it should work.  Should.

> I modified to the following hoping also to use both on 32 and 64 bit
> machines. Have I shot myself in the foot anyway? For example, is there a
> guarantee that the most significant limb is non-zero? Is there any
> possibility of this or some related function being added to Data.Bits?

> [snip code]

It's still not going to be portable because I'm hardwiring the GMP "nail
count" parameter to 0.  As for going standard - if you want this,
propose it!  I can't think of a sane implementation of Integer that
doesn't support some kind of approximate logarithm.

Stefan
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20080226/00fcf4ab/attachment.bin


More information about the Haskell-Cafe mailing list