Skip to content
Snippets Groups Projects
Commit 4af6126d authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

Use static array in zeroCount

parent 480a38d4
No related branches found
No related tags found
No related merge requests found
......@@ -33,13 +33,10 @@ default ()
#define TO64 integerToInt64#
toByte64# :: Int64# -> Int#
toByte64# i = word2Int# (and# 255## (int2Word# (int64ToInt# i)))
-- Double mantissae have 53 bits, too much for Int#
elim64# :: Int64# -> Int# -> (# Integer, Int# #)
elim64# n e =
case zeroCount (toByte64# n) of
case zeroCount (int64ToInt# n) of
t | isTrue# (e <=# t) -> (# integerFromInt64# (uncheckedIShiftRA64# n e), 0# #)
| isTrue# (t <# 8#) -> (# integerFromInt64# (uncheckedIShiftRA64# n t), e -# t #)
| otherwise -> elim64# (uncheckedIShiftRA64# n 8#) (e -# 8#)
......@@ -60,41 +57,13 @@ elimZerosInteger m e = elim64# (TO64 m) e
elimZerosInt# :: Int# -> Int# -> (# Integer, Int# #)
elimZerosInt# n e =
case zeroCount (toByte# n) of
case zeroCount n of
t | isTrue# (e <=# t) -> (# IS (uncheckedIShiftRA# n e), 0# #)
| isTrue# (t <# 8#) -> (# IS (uncheckedIShiftRA# n t), e -# t #)
| otherwise -> elimZerosInt# (uncheckedIShiftRA# n 8#) (e -# 8#)
{-# INLINE zeroCount #-}
-- | Number of trailing zero bits in a byte
zeroCount :: Int# -> Int#
zeroCount i =
case zeroCountArr of
BA ba -> indexInt8Array# ba i
toByte# :: Int# -> Int#
toByte# i = word2Int# (and# 255## (int2Word# i))
data BA = BA ByteArray#
-- Number of trailing zero bits in a byte
zeroCountArr :: BA
zeroCountArr =
let mkArr s =
case newByteArray# 256# s of
(# s1, mba #) ->
case writeInt8Array# mba 0# 8# s1 of
s2 ->
let fillA step val idx st
| isTrue# (idx <# 256#) =
case writeInt8Array# mba idx val st of
nx -> fillA step val (idx +# step) nx
| isTrue# (step <# 256#) =
fillA (2# *# step) (val +# 1#) step st
| otherwise = st
in case fillA 2# 0# 1# s2 of
s3 -> case unsafeFreezeByteArray# mba s3 of
(# _, ba #) -> ba
in case mkArr realWorld# of
b -> BA b
zeroCount i = indexInt8OffAddr# arr (word2Int# (narrow8Word# (int2Word# i))) -- index must be in [0,255]
where
arr = "\8\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\4\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\5\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\4\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\6\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\4\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\5\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\4\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\7\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\4\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\5\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\4\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\6\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\4\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\5\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0\4\0\1\0\2\0\1\0\3\0\1\0\2\0\1\0"#
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment