[Git][ghc/ghc][master] Use static array in zeroCount
Marge Bot
gitlab at gitlab.haskell.org
Sat Dec 12 03:44:19 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
4af6126d by Sylvain Henry at 2020-12-11T22:44:11-05:00
Use static array in zeroCount
- - - - -
1 changed file:
- libraries/base/GHC/Float/ConversionUtils.hs
Changes:
=====================================
libraries/base/GHC/Float/ConversionUtils.hs
=====================================
@@ -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"#
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4af6126d1758d5e365cadf032e34c99489f13dee
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4af6126d1758d5e365cadf032e34c99489f13dee
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20201211/379edd82/attachment-0001.html>
More information about the ghc-commits
mailing list